{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
module Dhall.TextShell (main) where
import Control.Exception (Handler (..), SomeException)
import Control.Monad (foldM)
import Control.Applicative (optional)
import Data.Text (Text)
import Data.Void (Void)
import Dhall.Core (Expr(Annot))
import Dhall.Import (SemanticCacheMode (..), Imported(..))
import Dhall.Parser (Src)
import Dhall.TypeCheck (Censored (..), DetailedTypeError (..), TypeError)
import Dhall.Util (Input (..), Output (..), Censor(..))
import Options.Applicative (Parser)
import System.Exit (ExitCode, exitFailure)
import qualified Control.Exception
import qualified Data.Map
import qualified Data.Text
import qualified Data.Text.IO
import qualified Dhall
import qualified Dhall.Core
import qualified Dhall.Import
import qualified Dhall.TypeCheck
import qualified Dhall.Util
import qualified GHC.IO.Encoding
import qualified Options.Applicative
import qualified System.FilePath
import qualified System.IO
import qualified System.Process
data AsCommand = AsCommand
{ AsCommand -> Censor
censor :: Censor
, AsCommand -> Bool
explain :: Bool
}
data Options = Options
{ Options -> Input
file :: Input
, Options -> Output
output :: Output
, Options -> [String]
argCmds :: [String]
}
parseConfig :: Parser (Options, AsCommand)
parseConfig :: Parser (Options, AsCommand)
parseConfig = (,) (Options -> AsCommand -> (Options, AsCommand))
-> Parser Options -> Parser (AsCommand -> (Options, AsCommand))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Options
parseOptions
Parser (AsCommand -> (Options, AsCommand))
-> Parser AsCommand -> Parser (Options, AsCommand)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser AsCommand
parseAsCommand
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
)
parseOptions :: Parser Options
parseOptions =
Input -> Output -> [String] -> Options
Options (Input -> Output -> [String] -> Options)
-> Parser Input -> Parser (Output -> [String] -> Options)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseFile
Parser (Output -> [String] -> Options)
-> Parser Output -> Parser ([String] -> Options)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Output
parseOutput
Parser ([String] -> Options) -> Parser [String] -> Parser Options
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String -> Parser [String]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
Options.Applicative.many Parser String
parseArgCmd
parseFile :: Parser Input
parseFile = (Maybe String -> Input) -> Parser (Maybe String) -> Parser Input
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"
)
parseOutput :: Parser Output
parseOutput = (Maybe String -> Output) -> Parser (Maybe String) -> Parser Output
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"
)
parseArgCmd :: Parser String
parseArgCmd = 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
"argCmd"
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
"Use shell command to supply as `Text -> Text` argument"
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
"CMD"
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
"CMD"
)
parseAsCommand :: Parser AsCommand
parseAsCommand =
Censor -> Bool -> AsCommand
AsCommand (Censor -> Bool -> AsCommand)
-> Parser Censor -> Parser (Bool -> AsCommand)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Censor
parseCensor
Parser (Bool -> AsCommand) -> Parser Bool -> Parser AsCommand
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"
parseCensor :: Parser Censor
parseCensor = (Bool -> Censor) -> Parser Bool -> Parser Censor
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
main :: IO ()
main :: IO ()
main = do
(Options
options, AsCommand
ac) <- ParserInfo (Options, AsCommand) -> IO (Options, AsCommand)
forall a. ParserInfo a -> IO a
Options.Applicative.execParser (ParserInfo (Options, AsCommand) -> IO (Options, AsCommand))
-> ParserInfo (Options, AsCommand) -> IO (Options, AsCommand)
forall a b. (a -> b) -> a -> b
$
Parser (Options, AsCommand)
-> InfoMod (Options, AsCommand) -> ParserInfo (Options, AsCommand)
forall a. Parser a -> InfoMod a -> ParserInfo a
Options.Applicative.info
(Parser ((Options, AsCommand) -> (Options, AsCommand))
forall a. Parser (a -> a)
Options.Applicative.helper Parser ((Options, AsCommand) -> (Options, AsCommand))
-> Parser (Options, AsCommand) -> Parser (Options, AsCommand)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Options, AsCommand)
parseConfig)
( String -> InfoMod (Options, AsCommand)
forall a. String -> InfoMod a
Options.Applicative.progDesc String
"render dhall text with shell commands as function arguments"
InfoMod (Options, AsCommand)
-> InfoMod (Options, AsCommand) -> InfoMod (Options, AsCommand)
forall a. Semigroup a => a -> a -> a
<> InfoMod (Options, AsCommand)
forall a. InfoMod a
Options.Applicative.fullDesc
)
AsCommand -> Options -> IO ()
runWithOptions AsCommand
ac Options
options
runWithOptions :: AsCommand -> Options -> IO ()
runWithOptions :: AsCommand -> Options -> IO ()
runWithOptions AsCommand
ac Options{[String]
Input
Output
argCmds :: [String]
output :: Output
file :: Input
argCmds :: Options -> [String]
output :: Options -> Output
file :: Options -> Input
..} = AsCommand
-> ((Input -> IO (Expr Src Import)) -> (Input -> String) -> IO ())
-> IO ()
asCommand AsCommand
ac (((Input -> IO (Expr Src Import)) -> (Input -> String) -> IO ())
-> IO ())
-> ((Input -> IO (Expr Src Import)) -> (Input -> String) -> IO ())
-> IO ()
forall a b. (a -> b) -> a -> b
$ \Input -> IO (Expr Src Import)
getExpression Input -> String
rootDirectory -> 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
let addPiLayer :: Expr Src Void -> Expr Src Void
addPiLayer :: Expr Src Void -> Expr Src Void
addPiLayer = Maybe CharacterSet
-> Text -> Expr Src Void -> Expr Src Void -> Expr Src Void
forall s a.
Maybe CharacterSet -> Text -> Expr s a -> Expr s a -> Expr s a
Dhall.Core.Pi
Maybe CharacterSet
forall a. Maybe a
Nothing Text
"_"
(Maybe CharacterSet
-> Text -> Expr Src Void -> Expr Src Void -> Expr Src Void
forall s a.
Maybe CharacterSet -> Text -> Expr s a -> Expr s a -> Expr s a
Dhall.Core.Pi Maybe CharacterSet
forall a. Maybe a
Nothing Text
"_" Expr Src Void
forall s a. Expr s a
Dhall.Core.Text Expr Src Void
forall s a. Expr s a
Dhall.Core.Text)
expectedType :: Expr Src Void
expectedType = (Expr Src Void -> Expr Src Void)
-> Expr Src Void -> [Expr Src Void]
forall a. (a -> a) -> a -> [a]
iterate Expr Src Void -> Expr Src Void
addPiLayer Expr Src Void
forall s a. Expr s a
Dhall.Core.Text [Expr Src Void] -> Int -> Expr Src Void
forall a. [a] -> Int -> a
!! [String] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
argCmds
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
expectedType))
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
peelArg :: (Expr Void Void, Data.Map.Map Text [String])
-> String
-> Maybe (Expr Void Void, Data.Map.Map Text [String])
peelArg :: (Expr Void Void, Map Text [String])
-> String -> Maybe (Expr Void Void, Map Text [String])
peelArg (Expr Void Void
currExp, Map Text [String]
currMap) String
arg = case Expr Void Void
currExp of
Dhall.Core.Lam Maybe CharacterSet
_ (Dhall.Core.FunctionBinding { Text
functionBindingVariable :: forall s a. FunctionBinding s a -> Text
functionBindingVariable :: Text
functionBindingVariable }) Expr Void Void
subExp ->
(Expr Void Void, Map Text [String])
-> Maybe (Expr Void Void, Map Text [String])
forall a. a -> Maybe a
Just (Expr Void Void
subExp, ([String] -> [String] -> [String])
-> Text -> [String] -> Map Text [String] -> Map Text [String]
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Data.Map.insertWith [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
(++) Text
functionBindingVariable [String
arg] Map Text [String]
currMap)
Expr Void Void
_ -> Maybe (Expr Void Void, Map Text [String])
forall a. Maybe a
Nothing
peeledExprAndMap :: Maybe (Expr Void Void, Map Text [String])
peeledExprAndMap =
((Expr Void Void, Map Text [String])
-> String -> Maybe (Expr Void Void, Map Text [String]))
-> (Expr Void Void, Map Text [String])
-> [String]
-> Maybe (Expr Void Void, Map Text [String])
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (Expr Void Void, Map Text [String])
-> String -> Maybe (Expr Void Void, Map Text [String])
peelArg (Expr Void Void
forall t. Expr t Void
normalizedExpression, Map Text [String]
forall k a. Map k a
Data.Map.empty) [String]
argCmds
case Maybe (Expr Void Void, Map Text [String])
peeledExprAndMap of
Maybe (Expr Void Void, Map Text [String])
Nothing -> () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Just (Expr Void Void
expr, Map Text [String]
argMap) -> do
Expr Void Void
res <- NormalizerM IO Void -> Expr Void Void -> IO (Expr Void Void)
forall (m :: * -> *) a s t.
(Monad m, Eq a) =>
NormalizerM m a -> Expr s a -> m (Expr t a)
Dhall.Core.normalizeWithM
(\Expr s Void
x -> case Expr s Void
x of
Dhall.Core.App (Dhall.Core.Var (Dhall.Core.V Text
v Int
i))
(Dhall.Core.TextLit (Dhall.Core.Chunks [] Text
txt))
| Just [String]
as <- Text -> Map Text [String] -> Maybe [String]
forall k a. Ord k => k -> Map k a -> Maybe a
Data.Map.lookup Text
v Map Text [String]
argMap
, String
a:[String]
_ <- Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
drop Int
i [String]
as
-> Expr s Void -> Maybe (Expr s Void)
forall a. a -> Maybe a
Just (Expr s Void -> Maybe (Expr s Void))
-> IO (Expr s Void) -> IO (Maybe (Expr s Void))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
Text
sysOut <- String -> Text
Data.Text.pack (String -> Text) -> IO String -> IO Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CreateProcess -> String -> IO String
System.Process.readCreateProcess
(String -> CreateProcess
System.Process.shell String
a)
(Text -> String
Data.Text.unpack Text
txt)
Expr s Void -> IO (Expr s Void)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Expr s Void -> IO (Expr s Void))
-> Expr s Void -> IO (Expr s Void)
forall a b. (a -> b) -> a -> b
$ Chunks s Void -> Expr s Void
forall s a. Chunks s a -> Expr s a
Dhall.Core.TextLit ([(Text, Expr s Void)] -> Text -> Chunks s Void
forall s a. [(Text, Expr s a)] -> Text -> Chunks s a
Dhall.Core.Chunks [] Text
sysOut)
Expr s Void
_ -> Maybe (Expr s Void) -> IO (Maybe (Expr s Void))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (Expr s Void)
forall a. Maybe a
Nothing
)
Expr Void Void
expr
case Expr Void Void
res 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
res
InvalidDecoder Void Void -> IO ()
forall e a. Exception e => e -> IO a
Control.Exception.throwIO (InvalidDecoder :: forall s a. Expr s a -> Expr s a -> InvalidDecoder s a
Dhall.InvalidDecoder {Expr Void Void
invalidDecoderExpected :: Expr Void Void
invalidDecoderExpression :: Expr Void Void
invalidDecoderExpression :: Expr Void Void
invalidDecoderExpected :: Expr Void Void
..})
asCommand
:: AsCommand
-> ((Input -> IO (Expr Src Dhall.Core.Import)) -> (Input -> FilePath) -> IO ())
-> IO ()
asCommand :: AsCommand
-> ((Input -> IO (Expr Src Import)) -> (Input -> String) -> IO ())
-> IO ()
asCommand AsCommand{Bool
Censor
explain :: Bool
censor :: Censor
explain :: AsCommand -> Bool
censor :: AsCommand -> Censor
..} (Input -> IO (Expr Src Import)) -> (Input -> String) -> IO ()
act = 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 getExpression :: Input -> IO (Expr Src Import)
getExpression = Censor -> Input -> IO (Expr Src Import)
Dhall.Util.getExpression Censor
censor
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 (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 (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)
IO () -> IO ()
forall a. IO a -> IO a
handle (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ (Input -> IO (Expr Src Import)) -> (Input -> String) -> IO ()
act Input -> IO (Expr Src Import)
getExpression Input -> String
rootDirectory