{-# 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
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Mode
parseMode
    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"
    forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> String -> String -> Parser Bool
switch String
"plain" String
"Disable syntax highlighting"
    forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe CharacterSet)
parseCharacterSet
    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
            (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
name
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
description
            )
    parseCensor :: Parser Censor
parseCensor = 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 =
            forall a. a -> Mod FlagFields a -> Parser a
Options.Applicative.flag'
                (forall a. a -> Maybe a
Just CharacterSet
Unicode)
                (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"unicode"
                forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Format code using only Unicode syntax"
                )
        forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall a. a -> Mod FlagFields a -> Parser a
Options.Applicative.flag'
                (forall a. a -> Maybe a
Just CharacterSet
ASCII)
                (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"ascii"
                forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Format code using only ASCII syntax"
                )
        forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall (f :: * -> *) a. Applicative f => a -> f a
pure 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 =
    forall a. Mod CommandFields a -> Parser a
Options.Applicative.hsubparser
        (   forall a. String -> ParserInfo a -> Mod CommandFields a
Options.Applicative.command String
name ParserInfo a
parserInfo
        forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar String
name
        forall a. Semigroup a => a -> a -> a
<>  forall a. String -> Mod CommandFields a
Options.Applicative.commandGroup (Group -> String
groupDescription Group
group)
        )
  where
    parserInfo :: ParserInfo a
parserInfo =
        forall a. Parser a -> InfoMod a -> ParserInfo a
Options.Applicative.info Parser a
parser
            (   forall a. InfoMod a
Options.Applicative.fullDesc
            forall a. Semigroup a => a -> a -> a
<>  forall a. String -> InfoMod a
Options.Applicative.progDesc String
description
            )
parseMode :: Parser Mode
parseMode :: Parser Mode
parseMode =
        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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Bool
deprecatedInPlace forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Transitivity
parseTransitiveSwitch forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> String -> Parser OutputMode
parseCheck String
"formatted" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (NonEmpty Input)
parseFiles)
    forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> 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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Bool
deprecatedInPlace forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Transitivity
parseTransitiveSwitch forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseAllFlag forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseCacheFlag forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> String -> Parser OutputMode
parseCheck String
"frozen" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (NonEmpty Input)
parseFiles)
    forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> 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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Bool
deprecatedInPlace forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Transitivity
parseTransitiveSwitch forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> String -> Parser OutputMode
parseCheck String
"linted" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (NonEmpty Input)
parseFiles)
    forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> 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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseInplaceNonTransitive forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> String -> Parser OutputMode
parseCheck String
"rewritten" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Text
parseSchemasRecord)
    forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> 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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseFile forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Output
parseOutput)
    forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> 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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Bool
parseDirectoryTreeAllowSeparators forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Input
parseFile forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String
parseDirectoryTreeOutput)
    forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> 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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseFile forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe ResolveMode)
parseResolveMode forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser SemanticCacheMode
parseSemanticCacheMode)
    forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> 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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseFile forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseQuiet forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser SemanticCacheMode
parseSemanticCacheMode)
    forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall a. Group -> String -> String -> Parser a -> Parser a
subcommand
            Group
Interpret
            String
"normalize"
            String
"Normalize an expression"
            (Input -> Bool -> Mode
Normalize forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseFile forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseAlpha)
    forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> 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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseFile forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseJSONFlag)
    forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> 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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseFile forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseJSONFlag forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseQuiet)
    forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall a. Group -> String -> String -> Parser a -> Parser a
subcommand
            Group
Miscellaneous
            String
"repl"
            String
"Interpret expressions in a REPL"
            (forall (f :: * -> *) a. Applicative f => a -> f a
pure Mode
Repl)
    forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> 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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> Parser Text
argument String
"expr1" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> String -> Parser Text
argument String
"expr2")
    forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> 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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseFile forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseCache)
    forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> 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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (Maybe String)
parsePackageName forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (NonEmpty String)
parsePackageFiles)
    forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> 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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseInput forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Output
parseTagsOutput forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe [Text])
parseSuffixes forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseFollowSymlinks)
    forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall a. Group -> String -> String -> Parser a -> Parser a
subcommand
            Group
Miscellaneous
            String
"version"
            String
"Display version"
            (forall (f :: * -> *) a. Applicative f => a -> f a
pure Mode
Version)
    forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> 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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseFile forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseNoted)
    forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (   Input
-> Output -> Bool -> Bool -> SemanticCacheMode -> Bool -> Mode
Default
        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseFile
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Output
parseOutput
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseAnnotate
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseAlpha
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser SemanticCacheMode
parseSemanticCacheMode
        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
            (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"inplace"
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. Mod f a
Options.Applicative.internal 
            )
    argument :: String -> Parser Text
argument =
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Text
Data.Text.pack
        forall b c a. (b -> c) -> (a -> b) -> a -> c
.   forall s. IsString s => Mod ArgumentFields s -> Parser s
Options.Applicative.strArgument
        forall b c a. (b -> c) -> (a -> b) -> a -> c
.   forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar
    parseFile :: Parser Input
parseFile = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe String -> Input
f (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 = forall s. IsString s => Mod OptionFields s -> Parser s
Options.Applicative.strOption
                (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"file"
                forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Read expression from a file instead of standard input"
                forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar String
"FILE"
                forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. HasCompleter f => String -> Mod f a
Options.Applicative.action String
"file"
                )
    parseFiles :: Parser (NonEmpty Input)
parseFiles = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [String] -> NonEmpty Input
f (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
"-" forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Input]
inputs = Input
StandardInput forall a. a -> [a] -> [a]
: forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Eq a => a -> a -> Bool
/= String -> Input
InputFile String
"-") [Input]
inputs
            | Bool
otherwise = [Input]
inputs
        f :: [String] -> NonEmpty Input
f = forall a. a -> Maybe a -> a
fromMaybe (forall (f :: * -> *) a. Applicative f => a -> f a
pure Input
StandardInput) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Maybe (NonEmpty a)
nonEmpty forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Input] -> [Input]
parseStdin forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Input
InputFile
        p :: Parser String
p = forall s. IsString s => Mod ArgumentFields s -> Parser s
Options.Applicative.strArgument
                (   forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Read expression from files instead of standard input"
                forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar String
"FILES"
                forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. HasCompleter f => String -> Mod f a
Options.Applicative.action String
"file"
                )
    parseOutput :: Parser Output
parseOutput = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe String -> Output
f (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 = forall s. IsString s => Mod OptionFields s -> Parser s
Options.Applicative.strOption
                (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"output"
                forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Write result to a file instead of standard output"
                forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar String
"FILE"
                forall a. Semigroup a => a -> a -> a
<>  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
            (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"alpha"
            forall a. Semigroup a => a -> a -> a
<>  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
            (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"annotate"
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Add a type annotation to the output"
            )
    parseSemanticCacheMode :: Parser SemanticCacheMode
parseSemanticCacheMode =
        forall a. a -> a -> Mod FlagFields a -> Parser a
Options.Applicative.flag
            SemanticCacheMode
UseSemanticCache
            SemanticCacheMode
IgnoreSemanticCache
            (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"no-cache"
            forall a. Semigroup a => a -> a -> a
<>  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
            (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"version"
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Display version"
            )
    parseResolveMode :: Parser (Maybe ResolveMode)
parseResolveMode =
          forall a. a -> Mod FlagFields a -> Parser a
Options.Applicative.flag' (forall a. a -> Maybe a
Just ResolveMode
Dot)
              (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"dot"
              forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help
                    String
"Output import dependency graph in dot format"
              )
        forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
          forall a. a -> Mod FlagFields a -> Parser a
Options.Applicative.flag' (forall a. a -> Maybe a
Just ResolveMode
ListImmediateDependencies)
              (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"immediate-dependencies"
              forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help
                    String
"List immediate import dependencies"
              )
        forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
          forall a. a -> Mod FlagFields a -> Parser a
Options.Applicative.flag' (forall a. a -> Maybe a
Just ResolveMode
ListTransitiveDependencies)
              (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"transitive-dependencies"
              forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help
                    String
"List transitive import dependencies in post-order"
              )
        forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
    parseQuiet :: Parser Bool
parseQuiet =
        Mod FlagFields Bool -> Parser Bool
Options.Applicative.switch
            (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"quiet"
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Don't print the result"
            )
    parseInplace :: Parser String
parseInplace =
        forall s. IsString s => Mod OptionFields s -> Parser s
Options.Applicative.strOption
            (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"inplace"
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Modify the specified file in-place"
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar String
"FILE"
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. HasCompleter f => String -> Mod f a
Options.Applicative.action String
"file"
            )
    parseTransitiveSwitch :: Parser Transitivity
parseTransitiveSwitch = forall a. a -> a -> Mod FlagFields a -> Parser a
Options.Applicative.flag Transitivity
NonTransitive Transitivity
Transitive
        (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"transitive"
        forall a. Semigroup a => a -> a -> a
<>  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 =
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Input
InputFile Parser String
parseInplace
        forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall (f :: * -> *) a. Applicative f => a -> f a
pure Input
StandardInput
    parseInput :: Parser Input
parseInput = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe String -> Input
f (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 = forall s. IsString s => Mod OptionFields s -> Parser s
Options.Applicative.strOption
            (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"path"
            forall a. Semigroup a => a -> a -> a
<>  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."
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar String
"PATH"
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. HasCompleter f => String -> Mod f a
Options.Applicative.action String
"file"
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. HasCompleter f => String -> Mod f a
Options.Applicative.action String
"directory"
            )
    parseTagsOutput :: Parser Output
parseTagsOutput = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe String -> Output
f (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 = forall s. IsString s => Mod OptionFields s -> Parser s
Options.Applicative.strOption
            (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"output"
            forall a. Semigroup a => a -> a -> a
<>  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\""
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar String
"FILENAME"
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. HasCompleter f => String -> Mod f a
Options.Applicative.action String
"file"
            )
    parseSuffixes :: Parser (Maybe [Text])
parseSuffixes = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe Text -> Maybe [Text]
f (forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser Text
p)
      where
        f :: Maybe Text -> Maybe [Text]
f  Maybe Text
Nothing    = forall a. a -> Maybe a
Just [Text
".dhall"]
        f (Just Text
"")   = forall a. Maybe a
Nothing
        f (Just Text
line) = forall a. a -> Maybe a
Just (Text -> Text -> [Text]
Data.Text.splitOn Text
" " Text
line)
        p :: Parser Text
p = forall s. IsString s => Mod OptionFields s -> Parser s
Options.Applicative.strOption
            (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"suffixes"
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Index only files with suffixes. \"\" to index all files."
            forall a. Semigroup a => a -> a -> a
<>  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
        (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"follow-symlinks"
        forall a. Semigroup a => a -> a -> a
<>  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
        (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"json"
        forall a. Semigroup a => a -> a -> a
<>  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
        (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"all"
        forall a. Semigroup a => a -> a -> a
<>  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
        (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"cache"
        forall a. Semigroup a => a -> a -> a
<>  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 = 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
            (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"check"
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help (String
"Only check if the input is " forall a. Semigroup a => a -> a -> a
<> String
processed)
            )
    parseSchemasRecord :: Parser Text
parseSchemasRecord =
        forall s. IsString s => Mod OptionFields s -> Parser s
Options.Applicative.strOption
            (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"schemas"
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"A record of schemas"
            forall a. Semigroup a => a -> a -> a
<>  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
            (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"allow-path-separators"
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Whether to allow path separators in file names"
            )
    parseDirectoryTreeOutput :: Parser String
parseDirectoryTreeOutput =
        forall s. IsString s => Mod OptionFields s -> Parser s
Options.Applicative.strOption
            (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"output"
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"The destination path to create"
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar String
"PATH"
            forall a. Semigroup a => a -> a -> a
<>  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
            (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"noted"
            forall a. Semigroup a => a -> a -> a
<>  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
            (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"cache"
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Cache the hashed expression"
            )
    parsePackageName :: Parser (Maybe String)
parsePackageName = forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional forall a b. (a -> b) -> a -> b
$
        forall s. IsString s => Mod OptionFields s -> Parser s
Options.Applicative.strOption
            (   forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"name"
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"The filename of the package"
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar String
"NAME"
            forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. HasCompleter f => String -> Mod f a
Options.Applicative.action String
"file"
            )
    parsePackageFiles :: Parser (NonEmpty String)
parsePackageFiles = forall a. a -> [a] -> NonEmpty a
(:|) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser String
p forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Alternative f => f a -> f [a]
Options.Applicative.many Parser String
p
      where
        p :: Parser String
p = forall s. IsString s => Mod ArgumentFields s -> Parser s
Options.Applicative.strArgument
                (   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."
                forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar String
"PATH"
                forall a. Semigroup a => a -> a -> a
<>  forall (f :: * -> *) a. HasCompleter f => String -> Mod f a
Options.Applicative.action String
"file"
                )
parserInfoOptions :: ParserInfo Options
parserInfoOptions :: ParserInfo Options
parserInfoOptions =
    forall a. Parser a -> InfoMod a -> ParserInfo a
Options.Applicative.info
        (forall a. Parser (a -> a)
Options.Applicative.helper forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Options
parseOptions)
        (   forall a. String -> InfoMod a
Options.Applicative.progDesc String
"Interpreter for the Dhall language"
        forall a. Semigroup a => a -> a -> a
<>  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
headers :: URL -> Maybe (Expr Src Import)
query :: URL -> Maybe Text
path :: URL -> File
authority :: URL -> Text
scheme :: URL -> Scheme
headers :: Maybe (Expr Src Import)
query :: Maybe Text
path :: File
authority :: Text
scheme :: Scheme
.. }, Maybe SHA256Digest
hash :: ImportHashed -> Maybe SHA256Digest
hash :: Maybe SHA256Digest
..}, ImportMode
importMode :: Import -> ImportMode
importMode :: ImportMode
.. }) =
    Import { importHashed :: ImportHashed
importHashed = ImportHashed { importType :: ImportType
importType = URL -> ImportType
Remote URL{ headers :: Maybe (Expr Src Import)
headers = forall a. Maybe a
Nothing, Maybe Text
Text
Scheme
File
query :: Maybe Text
path :: File
authority :: Text
scheme :: Scheme
query :: Maybe Text
path :: File
authority :: Text
scheme :: Scheme
.. }, 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
censor :: Censor
chosenCharacterSet :: Maybe CharacterSet
plain :: Bool
explain :: Bool
mode :: Mode
censor :: Options -> Censor
chosenCharacterSet :: Options -> Maybe CharacterSet
plain :: Options -> Bool
explain :: Options -> Bool
mode :: Options -> Mode
..}) = 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 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 = forall a. a -> Maybe a -> a
fromMaybe (forall a. Expr Src a -> CharacterSet
detectCharacterSet Expr Src Import
expr) Maybe CharacterSet
chosenCharacterSet
            forall (m :: * -> *) a. Monad m => a -> m a
return (Expr Src Import
expr, CharacterSet
characterSet)
    let handle :: IO a -> IO a
handle IO a
io =
            forall a. IO a -> [Handler a] -> IO a
Control.Exception.catches IO a
io
                [ forall a e. Exception e => (e -> IO a) -> Handler a
Handler forall {a}. TypeError Src X -> IO a
handleTypeError
                , forall a e. Exception e => (e -> IO a) -> Handler a
Handler forall {a}. Imported (TypeError Src X) -> IO a
handleImported
                , forall a e. Exception e => (e -> IO a) -> Handler a
Handler forall {a}. ExitCode -> IO a
handleExitCode
                ]
          where
            handleAll :: SomeException -> IO b
handleAll SomeException
e = do
                let string :: String
string = forall a. Show a => a -> String
show (SomeException
e :: SomeException)
                if Bool -> Bool
not (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 forall (m :: * -> *) a. Monad m => a -> m a
return ()
                forall a. IO a
System.Exit.exitFailure
            handleTypeError :: TypeError Src X -> IO a
handleTypeError TypeError Src X
e = forall e a. Exception e => (e -> IO a) -> IO a -> IO a
Control.Exception.handle forall {b}. SomeException -> IO b
handleAll forall a b. (a -> b) -> a -> b
$ do
                let TypeError Src X
_ = TypeError Src X
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   -> forall e a. Exception e => e -> IO a
Control.Exception.throwIO (DetailedTypeError Src X -> Censored
CensoredDetailed (forall s a. TypeError s a -> DetailedTypeError s a
DetailedTypeError TypeError Src X
e))
                            Censor
NoCensor -> forall e a. Exception e => e -> IO a
Control.Exception.throwIO (forall s a. TypeError s a -> DetailedTypeError s a
DetailedTypeError TypeError Src X
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   -> forall e a. Exception e => e -> IO a
Control.Exception.throwIO (TypeError Src X -> Censored
Censored TypeError Src X
e)
                            Censor
NoCensor -> forall e a. Exception e => e -> IO a
Control.Exception.throwIO TypeError Src X
e
            handleImported :: Imported (TypeError Src X) -> IO a
handleImported (Imported NonEmpty Chained
ps TypeError Src X
e) = forall e a. Exception e => (e -> IO a) -> IO a -> IO a
Control.Exception.handle forall {b}. SomeException -> IO b
handleAll forall a b. (a -> b) -> a -> b
$ do
                let TypeError Src X
_ = TypeError Src X
e :: TypeError Src Void
                Handle -> String -> IO ()
System.IO.hPutStrLn Handle
System.IO.stderr String
""
                if Bool
explain
                    then forall e a. Exception e => e -> IO a
Control.Exception.throwIO (forall e. NonEmpty Chained -> e -> Imported e
Imported NonEmpty Chained
ps (forall s a. TypeError s a -> DetailedTypeError s a
DetailedTypeError TypeError Src X
e))
                    else do
                        Handle -> Text -> IO ()
Data.Text.IO.hPutStrLn Handle
System.IO.stderr Text
"\ESC[2mUse \"dhall --explain\" for detailed errors\ESC[0m"
                        forall e a. Exception e => e -> IO a
Control.Exception.throwIO (forall e. NonEmpty Chained -> e -> Imported e
Imported NonEmpty Chained
ps TypeError Src X
e)
            handleExitCode :: ExitCode -> IO a
handleExitCode ExitCode
e =
                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 = 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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ann -> AnsiStyle
annToAnsiStyle SimpleDocStream Ann
stream
                    else 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 = 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 = forall ann. Doc ann -> SimpleDocStream ann
Dhall.Pretty.layout (Doc ann
doc forall a. Semigroup a => a -> a -> a
<> Doc ann
"\n")
            String -> Text -> IO ()
AtomicWrite.LazyText.atomicWriteFile String
file (forall ann. SimpleDocStream ann -> Text
Pretty.Text.renderLazy SimpleDocStream ann
stream)
    forall {a}. IO a -> IO a
handle forall a b. (a -> b) -> a -> b
$ case Mode
mode of
        Mode
Version ->
            String -> IO ()
putStrLn String
dhallVersionString
        Default {Bool
Output
Input
SemanticCacheMode
version :: Bool
semanticCacheMode :: SemanticCacheMode
alpha :: Bool
annotate :: Bool
output :: Output
file :: Input
version :: Mode -> Bool
semanticCacheMode :: Mode -> SemanticCacheMode
alpha :: Mode -> Bool
annotate :: Mode -> Bool
output :: Mode -> Output
file :: Mode -> Input
..} -> do
            if Bool
version
                then do
                    String -> IO ()
putStrLn String
dhallVersionString
                    forall a. IO a
Exit.exitSuccess
                else 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 X
resolvedExpression <-
                String -> SemanticCacheMode -> Expr Src Import -> IO (Expr Src X)
Dhall.Import.loadRelativeTo (Input -> String
rootDirectory Input
file) SemanticCacheMode
semanticCacheMode Expr Src Import
expression
            Expr Src X
inferredType <- forall e (io :: * -> *) a.
(Exception e, MonadIO io) =>
Either e a -> io a
Dhall.Core.throws (forall s. Expr s X -> Either (TypeError s X) (Expr s X)
Dhall.TypeCheck.typeOf Expr Src X
resolvedExpression)
            let normalizedExpression :: Expr t X
normalizedExpression = forall a s t. Eq a => Expr s a -> Expr t a
Dhall.Core.normalize Expr Src X
resolvedExpression
            let alphaNormalizedExpression :: Expr s X
alphaNormalizedExpression =
                    if Bool
alpha
                    then forall s a. Expr s a -> Expr s a
Dhall.Core.alphaNormalize forall {t}. Expr t X
normalizedExpression
                    else forall {t}. Expr t X
normalizedExpression
            let annotatedExpression :: Expr Src X
annotatedExpression =
                    if Bool
annotate
                        then forall s a. Expr s a -> Expr s a -> Expr s a
Annot forall {t}. Expr t X
alphaNormalizedExpression Expr Src X
inferredType
                        else forall {t}. Expr t X
alphaNormalizedExpression
            case Output
output of
                Output
StandardOutput -> forall a. Pretty a => Handle -> CharacterSet -> Expr Src a -> IO ()
render Handle
System.IO.stdout CharacterSet
characterSet Expr Src X
annotatedExpression
                OutputFile String
file_ ->
                    forall ann. String -> Doc ann -> IO ()
writeDocToFile
                        String
file_
                        (forall a. Pretty a => CharacterSet -> Expr Src a -> Doc Ann
Dhall.Pretty.prettyCharacterSet CharacterSet
characterSet Expr Src X
annotatedExpression)
        Resolve { resolveMode :: Mode -> Maybe ResolveMode
resolveMode = Just ResolveMode
Dot, Input
SemanticCacheMode
semanticCacheMode :: SemanticCacheMode
file :: Input
semanticCacheMode :: Mode -> SemanticCacheMode
file :: Mode -> Input
..} -> do
            Expr Src Import
expression <- Input -> IO (Expr Src Import)
getExpression Input
file
            (Dhall.Import.Types.Status { [Depends]
_graph :: Status -> [Depends]
_graph :: [Depends]
_graph, NonEmpty Chained
_stack :: Status -> NonEmpty Chained
_stack :: NonEmpty Chained
_stack }) <-
                forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m s
State.execStateT (Expr Src Import -> StateT Status IO (Expr Src X)
Dhall.Import.loadWith Expr Src Import
expression) (Input -> Status
toStatus Input
file) { _semanticCacheMode :: SemanticCacheMode
_semanticCacheMode = SemanticCacheMode
semanticCacheMode }
            let (Chained
rootImport :| [Chained]
_) = NonEmpty Chained
_stack
                imports :: [Chained]
imports = Chained
rootImport forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map Depends -> Chained
parent [Depends]
_graph forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map Depends -> Chained
child [Depends]
_graph
                importIds :: Map Chained NodeId
importIds = forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList (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 forall a b. (a -> b) -> a -> b
$ 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 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 (forall k a. Ord k => k -> Map k a -> Maybe a
Data.Map.lookup Chained
parent Map Chained NodeId
importIds, 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)
_                    -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
            let dot :: Dot ()
dot = do (String, String) -> Dot ()
Text.Dot.attribute (String
"rankdir", String
"LR")
                         forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Chained, NodeId) -> Dot ()
dotNode (forall k a. Map k a -> [(k, a)]
Data.Map.assocs Map Chained NodeId
importIds)
                         forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Depends -> Dot ()
dotEdge [Depends]
_graph
            String -> IO ()
putStr forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
"strict " forall a. Semigroup a => a -> a -> a
<>) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Dot a -> String
Text.Dot.showDot forall a b. (a -> b) -> a -> b
$ Dot ()
dot
        Resolve { resolveMode :: Mode -> Maybe ResolveMode
resolveMode = Just ResolveMode
ListImmediateDependencies, Input
SemanticCacheMode
semanticCacheMode :: SemanticCacheMode
file :: Input
semanticCacheMode :: Mode -> SemanticCacheMode
file :: Mode -> Input
..} -> do
            Expr Src Import
expression <- Input -> IO (Expr Src Import)
getExpression Input
file
            forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (forall a. Show a => a -> IO ()
print forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a ann. Pretty a => a -> Doc ann
Pretty.pretty 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
semanticCacheMode :: SemanticCacheMode
file :: Input
semanticCacheMode :: Mode -> SemanticCacheMode
file :: Mode -> Input
..} -> do
            Expr Src Import
expression <- Input -> IO (Expr Src Import)
getExpression Input
file
            (Dhall.Import.Types.Status { Map Chained ImportSemantics
_cache :: Status -> Map Chained ImportSemantics
_cache :: Map Chained ImportSemantics
_cache }) <-
                forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m s
State.execStateT (Expr Src Import -> StateT Status IO (Expr Src X)
Dhall.Import.loadWith Expr Src Import
expression) (Input -> Status
toStatus Input
file) { _semanticCacheMode :: SemanticCacheMode
_semanticCacheMode = SemanticCacheMode
semanticCacheMode }
            forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ forall a. Show a => a -> IO ()
print
                 forall b c a. (b -> c) -> (a -> b) -> a -> c
.   forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ( forall a ann. Pretty a => a -> Doc ann
Pretty.pretty
                          forall b c a. (b -> c) -> (a -> b) -> a -> c
. Import -> Import
noHeaders
                          forall b c a. (b -> c) -> (a -> b) -> a -> c
. Chained -> Import
Dhall.Import.chainedImport
                          )
                 forall b c a. (b -> c) -> (a -> b) -> a -> c
.   forall a. [a] -> [a]
reverse
                 forall b c a. (b -> c) -> (a -> b) -> a -> c
.   forall k v. Map k v -> [k]
Dhall.Map.keys
                 forall a b. (a -> b) -> a -> b
$   Map Chained ImportSemantics
_cache
        Resolve { resolveMode :: Mode -> Maybe ResolveMode
resolveMode = Maybe ResolveMode
Nothing, Input
SemanticCacheMode
semanticCacheMode :: SemanticCacheMode
file :: Input
semanticCacheMode :: Mode -> SemanticCacheMode
file :: Mode -> Input
..} -> do
            (Expr Src Import
expression, CharacterSet
characterSet) <- Input -> IO (Expr Src Import, CharacterSet)
getExpressionAndCharacterSet Input
file
            Expr Src X
resolvedExpression <-
                String -> SemanticCacheMode -> Expr Src Import -> IO (Expr Src X)
Dhall.Import.loadRelativeTo (Input -> String
rootDirectory Input
file) SemanticCacheMode
semanticCacheMode Expr Src Import
expression
            forall a. Pretty a => Handle -> CharacterSet -> Expr Src a -> IO ()
render Handle
System.IO.stdout CharacterSet
characterSet Expr Src X
resolvedExpression
        Normalize {Bool
Input
alpha :: Bool
file :: Input
alpha :: Mode -> Bool
file :: Mode -> Input
..} -> do
            (Expr Src Import
expression, CharacterSet
characterSet) <- Input -> IO (Expr Src Import, CharacterSet)
getExpressionAndCharacterSet Input
file
            Expr Src X
resolvedExpression <- forall (io :: * -> *).
MonadIO io =>
Expr Src Import -> io (Expr Src X)
Dhall.Import.assertNoImports Expr Src Import
expression
            Expr Src X
_ <- forall e (io :: * -> *) a.
(Exception e, MonadIO io) =>
Either e a -> io a
Dhall.Core.throws (forall s. Expr s X -> Either (TypeError s X) (Expr s X)
Dhall.TypeCheck.typeOf Expr Src X
resolvedExpression)
            let normalizedExpression :: Expr t X
normalizedExpression = forall a s t. Eq a => Expr s a -> Expr t a
Dhall.Core.normalize Expr Src X
resolvedExpression
            let alphaNormalizedExpression :: Expr s X
alphaNormalizedExpression =
                    if Bool
alpha
                    then forall s a. Expr s a -> Expr s a
Dhall.Core.alphaNormalize forall {t}. Expr t X
normalizedExpression
                    else forall {t}. Expr t X
normalizedExpression
            forall a. Pretty a => Handle -> CharacterSet -> Expr Src a -> IO ()
render Handle
System.IO.stdout CharacterSet
characterSet forall {t}. Expr t X
alphaNormalizedExpression
        Type {Bool
Input
SemanticCacheMode
semanticCacheMode :: SemanticCacheMode
quiet :: Bool
file :: Input
quiet :: Mode -> Bool
semanticCacheMode :: Mode -> SemanticCacheMode
file :: Mode -> Input
..} -> do
            (Expr Src Import
expression, CharacterSet
characterSet) <- Input -> IO (Expr Src Import, CharacterSet)
getExpressionAndCharacterSet Input
file
            Expr Src X
resolvedExpression <-
                String -> SemanticCacheMode -> Expr Src Import -> IO (Expr Src X)
Dhall.Import.loadRelativeTo (Input -> String
rootDirectory Input
file) SemanticCacheMode
semanticCacheMode Expr Src Import
expression
            Expr Src X
inferredType <- forall e (io :: * -> *) a.
(Exception e, MonadIO io) =>
Either e a -> io a
Dhall.Core.throws (forall s. Expr s X -> Either (TypeError s X) (Expr s X)
Dhall.TypeCheck.typeOf Expr Src X
resolvedExpression)
            if Bool
quiet
                then forall (m :: * -> *) a. Monad m => a -> m a
return ()
                else forall a. Pretty a => Handle -> CharacterSet -> Expr Src a -> IO ()
render Handle
System.IO.stdout CharacterSet
characterSet Expr Src X
inferredType
        Mode
Repl ->
            CharacterSet -> Bool -> IO ()
Dhall.Repl.repl
                (forall a. a -> Maybe a -> a
fromMaybe CharacterSet
Unicode Maybe CharacterSet
chosenCharacterSet) 
                Bool
explain
        Diff {Text
expr2 :: Text
expr1 :: Text
expr2 :: Mode -> Text
expr1 :: Mode -> Text
..} -> do
            Expr Src X
expression1 <- Text -> IO (Expr Src X)
Dhall.inputExpr Text
expr1
            Expr Src X
expression2 <- Text -> IO (Expr Src X)
Dhall.inputExpr Text
expr2
            let diff :: Diff
diff = forall a s. (Eq a, Pretty a) => Expr s a -> Expr s a -> Diff
Dhall.Diff.diffNormalized Expr Src X
expression1 Expr Src X
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 forall (m :: * -> *) a. Monad m => a -> m a
return ()
                else forall a. IO a
Exit.exitFailure
        Format {Bool
NonEmpty Input
OutputMode
Transitivity
inputs :: NonEmpty Input
outputMode :: OutputMode
transitivity :: Transitivity
deprecatedInPlace :: Bool
inputs :: Mode -> NonEmpty Input
outputMode :: Mode -> OutputMode
transitivity :: Mode -> Transitivity
deprecatedInPlace :: Mode -> Bool
..} -> do
            forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
deprecatedInPlace 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
outputMode :: OutputMode
inputs :: NonEmpty Input
transitivity :: Transitivity
censor :: Censor
chosenCharacterSet :: Maybe CharacterSet
inputs :: NonEmpty Input
outputMode :: OutputMode
transitivity :: Transitivity
censor :: Censor
chosenCharacterSet :: Maybe CharacterSet
..}
        Freeze {Bool
NonEmpty Input
OutputMode
Transitivity
inputs :: NonEmpty Input
outputMode :: OutputMode
cache :: Bool
all_ :: Bool
transitivity :: Transitivity
deprecatedInPlace :: Bool
cache :: Mode -> Bool
all_ :: Mode -> Bool
inputs :: Mode -> NonEmpty Input
outputMode :: Mode -> OutputMode
transitivity :: Mode -> Transitivity
deprecatedInPlace :: Mode -> Bool
..} -> do
            forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
deprecatedInPlace 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
cache :: Bool
file :: Input
cache :: Mode -> Bool
file :: Mode -> Input
..} -> do
            Expr Src Import
expression <- Input -> IO (Expr Src Import)
getExpression Input
file
            Expr Src X
resolvedExpression <-
                String -> SemanticCacheMode -> Expr Src Import -> IO (Expr Src X)
Dhall.Import.loadRelativeTo (Input -> String
rootDirectory Input
file) SemanticCacheMode
UseSemanticCache Expr Src Import
expression
            Expr Src X
_ <- forall e (io :: * -> *) a.
(Exception e, MonadIO io) =>
Either e a -> io a
Dhall.Core.throws (forall s. Expr s X -> Either (TypeError s X) (Expr s X)
Dhall.TypeCheck.typeOf Expr Src X
resolvedExpression)
            let normalizedExpression :: Expr s X
normalizedExpression =
                    forall s a. Expr s a -> Expr s a
Dhall.Core.alphaNormalize (forall a s t. Eq a => Expr s a -> Expr t a
Dhall.Core.normalize Expr Src X
resolvedExpression)
            if Bool
cache
                then Expr X X -> IO ()
Dhall.Import.writeExpressionToSemanticCache forall {t}. Expr t X
normalizedExpression
                else forall (m :: * -> *) a. Monad m => a -> m a
return ()
            Text -> IO ()
Data.Text.IO.putStrLn (Expr X X -> Text
Dhall.Import.hashExpressionToCode Expr X X
normalizedExpression)
        Lint { transitivity :: Mode -> Transitivity
transitivity = Transitivity
transitivity0, Bool
NonEmpty Input
OutputMode
inputs :: NonEmpty Input
outputMode :: OutputMode
deprecatedInPlace :: Bool
inputs :: Mode -> NonEmpty Input
outputMode :: Mode -> OutputMode
deprecatedInPlace :: Mode -> Bool
..} -> do
            forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
deprecatedInPlace forall a b. (a -> b) -> a -> b
$
                Handle -> String -> IO ()
System.IO.hPutStrLn Handle
System.IO.stderr String
"Warning: the flag \"--inplace\" is deprecated"
            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 = forall a. a -> Maybe a -> a
fromMaybe (forall a. Expr Src a -> CharacterSet
detectCharacterSet Expr Src Import
parsedExpression) Maybe CharacterSet
chosenCharacterSet
                case Transitivity
transitivity of
                    Transitivity
Transitive ->
                        forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ Expr Src Import
parsedExpression 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_
                            forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ Maybe String
maybeFilepath forall a b. (a -> b) -> a -> b
$ \String
filepath ->
                                Input -> IO (Either CheckFailed ())
go (String -> Input
InputFile String
filepath)
                    Transitivity
NonTransitive ->
                        forall (m :: * -> *) a. Monad m => a -> m a
return ()
                let lintedExpression :: Expr Src Import
lintedExpression = forall s. Eq s => Expr s Import -> Expr s Import
Dhall.Lint.lint Expr Src Import
parsedExpression
                let doc :: Doc Ann
doc =   forall a ann. Pretty a => a -> Doc ann
Pretty.pretty Text
header
                        forall a. Semigroup a => a -> a -> a
<>  forall a. Pretty a => CharacterSet -> Expr Src a -> Doc Ann
Dhall.Pretty.prettyCharacterSet CharacterSet
characterSet Expr Src Import
lintedExpression
                let stream :: SimpleDocStream Ann
stream = forall ann. Doc ann -> SimpleDocStream ann
Dhall.Pretty.layout Doc Ann
doc
                let modifiedText :: Text
modifiedText = forall ann. SimpleDocStream ann -> Text
Pretty.Text.renderStrict SimpleDocStream Ann
stream 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 forall a. Eq a => a -> a -> Bool
== Text
modifiedText
                                    then forall (m :: * -> *) a. Monad m => a -> m a
return ()
                                    else forall ann. 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 (forall a b. b -> Either a b
Right ())
                    OutputMode
Check ->
                        forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
                            if Text
originalText forall a. Eq a => a -> a -> Bool
== Text
modifiedText
                                then forall a b. b -> Either a b
Right ()
                                else forall a b. a -> Either a b
Left CheckFailed{Input
input :: Input
input :: Input
..}
        Encode {Bool
Input
json :: Bool
file :: Input
json :: Mode -> Bool
file :: Mode -> Input
..} -> do
            Expr Src Import
expression <- Input -> IO (Expr Src Import)
getExpression Input
file
            let bytes :: ByteString
bytes = forall a. Serialise (Expr X a) => Expr X a -> ByteString
Dhall.Binary.encodeExpression (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 = forall s. Bool -> Decoder s Value
Codec.CBOR.JSON.decodeValue Bool
False
                    (ByteString
_, Value
value) <- forall e (io :: * -> *) a.
(Exception e, MonadIO io) =>
Either e a -> io a
Dhall.Core.throws (forall a.
(forall s. Decoder s a)
-> ByteString -> Either DeserialiseFailure (ByteString, a)
Codec.CBOR.Read.deserialiseFromBytes forall {s}. Decoder s Value
decoder ByteString
bytes)
                    let jsonBytes :: ByteString
jsonBytes = 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
quiet :: Bool
json :: Bool
file :: Input
json :: Mode -> Bool
quiet :: Mode -> Bool
file :: Mode -> Input
..} -> 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 X Import
expression <-
                if Bool
json
                    then do
                        Value
value <- case forall a. FromJSON a => ByteString -> Either String a
Data.Aeson.eitherDecode' ByteString
bytes of
                            Left  String
string -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
string
                            Right Value
value  -> 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
                        forall e (io :: * -> *) a.
(Exception e, MonadIO io) =>
Either e a -> io a
Dhall.Core.throws (forall s a.
Serialise (Expr s a) =>
ByteString -> Either DecodingFailure (Expr s a)
Dhall.Binary.decodeExpression ByteString
cborgBytes)
                    else
                        forall e (io :: * -> *) a.
(Exception e, MonadIO io) =>
Either e a -> io a
Dhall.Core.throws (forall s a.
Serialise (Expr s a) =>
ByteString -> Either DecodingFailure (Expr s a)
Dhall.Binary.decodeExpression ByteString
bytes)
            if Bool
quiet
                then forall (m :: * -> *) a. Monad m => a -> m a
return ()
                else do
                    let doc :: Doc Ann
doc =
                            forall a. Pretty a => CharacterSet -> Expr Src a -> Doc Ann
Dhall.Pretty.prettyCharacterSet
                                (forall a. a -> Maybe a -> a
fromMaybe CharacterSet
Unicode Maybe CharacterSet
chosenCharacterSet) 
                                (forall a s. Expr X a -> Expr s a
Dhall.Core.renote Expr X Import
expression :: Expr Src Import)
                    Handle -> Doc Ann -> IO ()
renderDoc Handle
System.IO.stdout Doc Ann
doc
        Text {Output
Input
output :: Output
file :: Input
output :: Mode -> Output
file :: Mode -> Input
..} -> do
            Expr Src Import
expression <- Input -> IO (Expr Src Import)
getExpression Input
file
            Expr Src X
resolvedExpression <-
                String -> SemanticCacheMode -> Expr Src Import -> IO (Expr Src X)
Dhall.Import.loadRelativeTo (Input -> String
rootDirectory Input
file) SemanticCacheMode
UseSemanticCache Expr Src Import
expression
            Expr Src X
_ <- forall e (io :: * -> *) a.
(Exception e, MonadIO io) =>
Either e a -> io a
Dhall.Core.throws (forall s. Expr s X -> Either (TypeError s X) (Expr s X)
Dhall.TypeCheck.typeOf (forall s a. Expr s a -> Expr s a -> Expr s a
Annot Expr Src X
resolvedExpression forall s a. Expr s a
Dhall.Core.Text))
            let normalizedExpression :: Expr t X
normalizedExpression = forall a s t. Eq a => Expr s a -> Expr t a
Dhall.Core.normalize Expr Src X
resolvedExpression
            case forall {t}. Expr t X
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 Any X
_ -> do
                    let invalidDecoderExpected :: Expr Void Void
                        invalidDecoderExpected :: Expr X X
invalidDecoderExpected = forall s a. Expr s a
Dhall.Core.Text
                    let invalidDecoderExpression :: Expr Void Void
                        invalidDecoderExpression :: Expr X X
invalidDecoderExpression = forall {t}. Expr t X
normalizedExpression
                    forall e a. Exception e => e -> IO a
Control.Exception.throwIO (Dhall.InvalidDecoder {Expr X X
invalidDecoderExpression :: Expr X X
invalidDecoderExpected :: Expr X X
invalidDecoderExpression :: Expr X X
invalidDecoderExpected :: Expr X X
..})
        Tags {Bool
Maybe [Text]
Output
Input
followSymlinks :: Bool
suffixes :: Maybe [Text]
output :: Output
input :: Input
followSymlinks :: Mode -> Bool
suffixes :: Mode -> Maybe [Text]
input :: Mode -> Input
output :: Mode -> Output
..} -> 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 ->
                    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
path :: String
file :: Input
allowSeparators :: Bool
path :: Mode -> String
allowSeparators :: Mode -> Bool
file :: Mode -> Input
..} -> do
            Expr Src Import
expression <- Input -> IO (Expr Src Import)
getExpression Input
file
            Expr Src X
resolvedExpression <-
                String -> SemanticCacheMode -> Expr Src Import -> IO (Expr Src X)
Dhall.Import.loadRelativeTo (Input -> String
rootDirectory Input
file) SemanticCacheMode
UseSemanticCache Expr Src Import
expression
            Expr Src X
_ <- forall e (io :: * -> *) a.
(Exception e, MonadIO io) =>
Either e a -> io a
Dhall.Core.throws (forall s. Expr s X -> Either (TypeError s X) (Expr s X)
Dhall.TypeCheck.typeOf Expr Src X
resolvedExpression)
            let normalizedExpression :: Expr t X
normalizedExpression = forall a s t. Eq a => Expr s a -> Expr t a
Dhall.Core.normalize Expr Src X
resolvedExpression
            Bool -> String -> Expr X X -> IO ()
DirectoryTree.toDirectoryTree Bool
allowSeparators String
path forall {t}. Expr t X
normalizedExpression
        Dhall.Main.Schemas{Text
OutputMode
Input
schemas :: Text
outputMode :: OutputMode
file :: Input
schemas :: Mode -> Text
outputMode :: Mode -> OutputMode
file :: Mode -> Input
..} ->
            Schemas -> IO ()
Dhall.Schemas.schemasCommand Dhall.Schemas.Schemas{ input :: Input
input = Input
file, Maybe CharacterSet
Text
OutputMode
Censor
schemas :: Text
outputMode :: OutputMode
censor :: Censor
chosenCharacterSet :: Maybe CharacterSet
schemas :: Text
outputMode :: OutputMode
censor :: Censor
chosenCharacterSet :: Maybe CharacterSet
..}
        SyntaxTree {Bool
Input
noted :: Bool
file :: Input
noted :: Mode -> Bool
file :: Mode -> Input
..} -> do
            Expr Src Import
expression <- Input -> IO (Expr Src Import)
getExpression Input
file
            if Bool
noted then
                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 X Import
denoted = forall s a t. Expr s a -> Expr t a
Dhall.Core.denote Expr Src Import
expression
                in forall (m :: * -> *) a. (MonadIO m, Show a) => a -> m ()
Text.Pretty.Simple.pPrintNoColor Expr X Import
denoted
        Package {Maybe String
NonEmpty String
files :: NonEmpty String
name :: Maybe String
files :: Mode -> NonEmpty String
name :: Mode -> Maybe String
..} -> CharacterSet -> Maybe String -> NonEmpty String -> IO ()
writePackage (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 <- forall a. ParserInfo a -> IO a
Options.Applicative.execParser ParserInfo Options
parserInfoOptions
    Options -> IO ()
Dhall.Main.command Options
options