Use (stdin) and (input) in Trifecta error messages

... instead of `(interactive)`
This commit is contained in:
Gabriel Gonzalez 2016-11-03 09:40:29 -07:00
parent 10d67551ea
commit e3850beed6
5 changed files with 21 additions and 11 deletions

View File

@ -70,4 +70,5 @@ Executable dhall
bytestring < 0.11,
dhall ,
optparse-applicative < 0.13,
trifecta,
text >= 0.11.1.0 && < 1.3

View File

@ -1,3 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Control.Exception (Exception, throwIO)
@ -9,6 +11,7 @@ import Dhall.Parser (exprFromText)
import Options.Applicative hiding (Const)
import System.IO (stderr)
import System.Exit (exitFailure)
import Text.Trifecta.Delta (Delta(..))
import qualified Data.Text.Lazy.IO
import qualified Dhall.TypeCheck
@ -69,10 +72,13 @@ main = do
\program's normalized type to standard error, and writing \
\the normalized program to standard output."
)
let delta = Directed "(stdin)" 0 0 0 0
case mode of
Default -> do
inText <- Data.Text.Lazy.IO.getContents
expr <- throws (exprFromText inText)
expr <- throws (exprFromText delta inText)
expr' <- load Nothing expr
typeExpr <- throws (Dhall.TypeCheck.typeOf expr')
Data.Text.Lazy.IO.hPutStrLn stderr (pretty (normalize typeExpr))
@ -80,12 +86,12 @@ main = do
Data.Text.Lazy.IO.putStrLn (pretty (normalize expr'))
Resolve -> do
inText <- Data.Text.Lazy.IO.getContents
expr <- throws (exprFromText inText)
expr <- throws (exprFromText delta inText)
expr' <- load Nothing expr
Data.Text.Lazy.IO.putStrLn (pretty expr')
TypeCheck -> do
inText <- Data.Text.Lazy.IO.getContents
expr <- throws (exprFromText inText)
expr <- throws (exprFromText delta inText)
case traverse (\_ -> Nothing) expr of
Nothing -> throwIO (userError
"`dhall typecheck` cannot type-check a program containing \
@ -97,5 +103,5 @@ main = do
Data.Text.Lazy.IO.putStrLn (pretty typeExpr)
Normalize -> do
inText <- Data.Text.Lazy.IO.getContents
expr <- throws (exprFromText inText)
expr <- throws (exprFromText delta inText)
Data.Text.Lazy.IO.putStrLn (pretty (normalize expr))

View File

@ -322,6 +322,7 @@ import Dhall.TypeCheck (X)
import GHC.Generics
import Numeric.Natural (Natural)
import Prelude hiding (maybe)
import Text.Trifecta.Delta (Delta(..))
import qualified Control.Exception
import qualified Data.Map
@ -361,7 +362,8 @@ input
-> IO a
-- ^ The decoded value in Haskell
input (Type {..}) text = do
expr <- throws (Dhall.Parser.exprFromText text)
let delta = Directed "(input)" 0 0 0 0
expr <- throws (Dhall.Parser.exprFromText delta text)
expr' <- Dhall.Import.load Nothing expr
typeExpr <- throws (Dhall.TypeCheck.typeOf (Annot expr' expected))
case extract (Dhall.Core.normalize expr') of

View File

@ -371,9 +371,9 @@ exprFromURL m url = do
Left _ -> throwIO err'
Right text' -> return text'
case Dhall.Parser.exprFromText text' of
Left _ -> throwIO err'
Right expr -> return expr
case Text.Trifecta.parseString parser delta (Text.unpack text') of
Failure _ -> throwIO err'
Success expr -> return expr
Success expr -> return expr
where
parser = do

View File

@ -65,6 +65,7 @@ instance Buildable Src where
build text <> "\n"
<> "\n"
<> build (show (Text.PrettyPrint.ANSI.Leijen.pretty begin))
<> "\n"
where
bytes' = Data.ByteString.Lazy.fromStrict bytes
@ -672,8 +673,8 @@ instance Show ParseError where
instance Exception ParseError
-- | Parse an expression from `Text` containing a Dhall program
exprFromText :: Text -> Either ParseError (Expr Src Path)
exprFromText text = case result of
exprFromText :: Delta -> Text -> Either ParseError (Expr Src Path)
exprFromText delta text = case result of
Success r -> Right r
Failure errInfo -> Left (ParseError (Text.Trifecta._errDoc errInfo))
where
@ -685,4 +686,4 @@ exprFromText text = case result of
Text.Parser.Combinators.eof
return r
result = Text.Trifecta.parseString parser mempty string
result = Text.Trifecta.parseString parser delta string