mirror of
https://github.com/GaloisInc/cryptol.git
synced 2024-12-27 09:53:34 +03:00
prepare for 7.10
- Move the stackage file so it's not on by default (will test with it on Jenkins instead of all the time) - Use CPP to remove unnecessary import warnings in 7.10
This commit is contained in:
parent
a07980b652
commit
8007f97205
@ -30,6 +30,15 @@ as regression tests. The test suite itself is written using the
|
||||
`test-framework` library, so it can readily output XML for consumption
|
||||
by Jenkins and other CI systems.
|
||||
|
||||
## Stackage
|
||||
|
||||
On the Jenkins machines, we `cp stackage.config cabal.config` before
|
||||
building in order to build against a Stackage LTS snapshot (updated
|
||||
periodically). This is to ensure compatibility with downstream
|
||||
dependencies that rely on Stackage for their stability. We do not have
|
||||
`cabal.config` in place by default, though, so developers can use
|
||||
different versions of the compiler.
|
||||
|
||||
## Running tests
|
||||
|
||||
To run the test suite, run `make test` from the root of the
|
||||
|
@ -151,8 +151,9 @@ library
|
||||
Paths_cryptol,
|
||||
GitRev
|
||||
|
||||
default-extensions: CPP
|
||||
GHC-options: -Wall -O2
|
||||
ghc-prof-options: -fprof-auto -prof
|
||||
ghc-prof-options: -fprof-auto -prof
|
||||
|
||||
if flag(relocatable)
|
||||
cpp-options: -DRELOCATABLE
|
||||
@ -184,8 +185,9 @@ executable cryptol
|
||||
, sbv
|
||||
, tf-random
|
||||
, transformers
|
||||
default-extensions: CPP
|
||||
GHC-options: -Wall -O2
|
||||
ghc-prof-options: -auto-all -prof -rtsopts
|
||||
ghc-prof-options: -auto-all -prof -rtsopts
|
||||
|
||||
if os(linux) && flag(static)
|
||||
ld-options: -static -pthread
|
||||
|
@ -27,7 +27,6 @@ import Cryptol.Version (commitHash, commitBranch, commitDirty)
|
||||
import Paths_cryptol (version)
|
||||
|
||||
import Data.Version (showVersion)
|
||||
import Data.Monoid (mconcat)
|
||||
import GHC.IO.Encoding (setLocaleEncoding, utf8)
|
||||
import System.Console.GetOpt
|
||||
(OptDescr(..),ArgOrder(..),ArgDescr(..),getOpt,usageInfo)
|
||||
@ -35,6 +34,10 @@ import System.Environment (getArgs, getProgName, lookupEnv)
|
||||
import System.Exit (exitFailure)
|
||||
import System.FilePath (searchPathSeparator, splitSearchPath, takeDirectory)
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Data.Monoid (mconcat)
|
||||
#endif
|
||||
|
||||
data Options = Options
|
||||
{ optLoad :: [FilePath]
|
||||
, optVersion :: Bool
|
||||
|
@ -9,7 +9,11 @@
|
||||
|
||||
module OptParser where
|
||||
|
||||
import Data.Monoid (Endo(..),Monoid(..))
|
||||
import Data.Monoid (Endo(..))
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Data.Monoid (Monoid(..))
|
||||
#endif
|
||||
|
||||
data OptParser opt
|
||||
= OptSuccess (Endo opt)
|
||||
|
@ -29,9 +29,11 @@ import Cryptol.Utils.PP
|
||||
import Cryptol.Prims.Eval
|
||||
|
||||
import Data.List (transpose)
|
||||
import Data.Monoid (Monoid(..),mconcat)
|
||||
import qualified Data.Map as Map
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Data.Monoid (Monoid(..),mconcat)
|
||||
#endif
|
||||
|
||||
-- Expression Evaluation -------------------------------------------------------
|
||||
|
||||
|
@ -15,9 +15,11 @@ import Cryptol.Eval.Value
|
||||
import Cryptol.TypeCheck.AST
|
||||
import Cryptol.Utils.PP
|
||||
|
||||
import Data.Monoid (Monoid(..))
|
||||
import qualified Data.Map as Map
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Data.Monoid (Monoid(..))
|
||||
#endif
|
||||
|
||||
-- Evaluation Environment ------------------------------------------------------
|
||||
|
||||
@ -62,6 +64,3 @@ bindType p ty env = env { envTypes = Map.insert p ty (envTypes env) }
|
||||
-- | Lookup a type variable.
|
||||
lookupType :: TVar -> EvalEnv -> Maybe TValue
|
||||
lookupType p env = Map.lookup p (envTypes env)
|
||||
|
||||
|
||||
|
||||
|
@ -33,7 +33,6 @@ import Cryptol.Transform.MonoValues
|
||||
import Control.DeepSeq
|
||||
import qualified Control.Exception as X
|
||||
import Control.Monad (unless)
|
||||
import Data.Foldable (foldMap)
|
||||
import Data.Function (on)
|
||||
import Data.List (nubBy)
|
||||
import Data.Maybe (mapMaybe,fromMaybe)
|
||||
@ -49,6 +48,10 @@ import System.FilePath ( addExtension
|
||||
import qualified System.IO.Error as IOE
|
||||
import qualified Data.Map as Map
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Data.Foldable (foldMap)
|
||||
#endif
|
||||
|
||||
-- Renaming --------------------------------------------------------------------
|
||||
|
||||
rename :: R.Rename a => R.NamingEnv -> a -> ModuleM a
|
||||
|
@ -26,12 +26,16 @@ import Control.Monad (guard)
|
||||
import Data.Foldable (fold)
|
||||
import Data.Function (on)
|
||||
import qualified Data.Map as Map
|
||||
import Data.Monoid ((<>), Monoid(..))
|
||||
import Data.Monoid ((<>))
|
||||
import System.Directory (getAppUserDataDirectory, getCurrentDirectory)
|
||||
import System.Environment(getExecutablePath)
|
||||
import System.FilePath ((</>), normalise, joinPath, splitPath, takeDirectory)
|
||||
import qualified Data.List as List
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Data.Monoid (Monoid(..))
|
||||
#endif
|
||||
|
||||
-- Module Environment ----------------------------------------------------------
|
||||
|
||||
data ModuleEnv = ModuleEnv
|
||||
|
@ -24,8 +24,10 @@ import Cryptol.Parser.AST (mkQual)
|
||||
import Cryptol.TypeCheck.AST
|
||||
|
||||
import qualified Data.Map as Map
|
||||
import Data.Monoid (Monoid(..))
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Data.Monoid (Monoid(..))
|
||||
#endif
|
||||
|
||||
-- | The resulting interface generated by a module that has been typechecked.
|
||||
data Iface = Iface
|
||||
|
@ -25,12 +25,14 @@ import qualified Cryptol.TypeCheck.AST as T
|
||||
import Cryptol.Parser.Position (Range)
|
||||
import Cryptol.Utils.PP
|
||||
|
||||
import Control.Applicative (Applicative(..))
|
||||
import Control.Exception (IOException)
|
||||
import Data.Function (on)
|
||||
import Data.Maybe (isJust)
|
||||
import MonadLib
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative (Applicative(..))
|
||||
#endif
|
||||
|
||||
-- Errors ----------------------------------------------------------------------
|
||||
|
||||
|
@ -16,12 +16,14 @@ import qualified Cryptol.TypeCheck.AST as T
|
||||
import Cryptol.Utils.PP
|
||||
import Cryptol.Utils.Panic (panic)
|
||||
|
||||
import qualified Data.Map as Map
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative (Applicative, (<$>), (<*>))
|
||||
import Data.Monoid (Monoid(..))
|
||||
import Data.Foldable (foldMap)
|
||||
import Data.Traversable (traverse)
|
||||
import qualified Data.Map as Map
|
||||
|
||||
#endif
|
||||
|
||||
-- Name Locations --------------------------------------------------------------
|
||||
|
||||
|
@ -26,13 +26,15 @@ import Cryptol.Parser.Position
|
||||
import Cryptol.Utils.Panic (panic)
|
||||
import Cryptol.Utils.PP
|
||||
|
||||
import MonadLib
|
||||
import qualified Data.Map as Map
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative(Applicative(..),(<$>))
|
||||
import Data.Foldable (foldMap)
|
||||
import Data.Monoid (Monoid(..))
|
||||
import Data.Traversable (traverse)
|
||||
import MonadLib
|
||||
import qualified Data.Map as Map
|
||||
|
||||
#endif
|
||||
|
||||
-- Errors ----------------------------------------------------------------------
|
||||
|
||||
|
@ -68,9 +68,12 @@ import qualified Data.Set as Set
|
||||
import Data.List(intersperse)
|
||||
import Data.Bits(shiftR)
|
||||
import Data.Maybe (catMaybes)
|
||||
import Data.Monoid (Monoid(..))
|
||||
import Numeric(showIntAtBase)
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Data.Monoid (Monoid(..))
|
||||
#endif
|
||||
|
||||
-- | Module names are just namespaces.
|
||||
--
|
||||
-- INVARIANT: the list of strings should never be empty in a valid module name.
|
||||
|
@ -21,12 +21,14 @@ import Cryptol.Utils.PP
|
||||
import Cryptol.Utils.Panic(panic)
|
||||
|
||||
import MonadLib
|
||||
import Control.Applicative(Applicative(..),(<$>))
|
||||
import Data.Maybe(maybeToList)
|
||||
import Data.Either(partitionEithers)
|
||||
import qualified Data.Map as Map
|
||||
import Data.Traversable(traverse)
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative(Applicative(..),(<$>))
|
||||
import Data.Traversable(traverse)
|
||||
#endif
|
||||
|
||||
class RemovePatterns t where
|
||||
-- | Eliminate all patterns in a program.
|
||||
|
@ -19,9 +19,13 @@ import Cryptol.Utils.Panic
|
||||
|
||||
import Data.Maybe(listToMaybe,fromMaybe)
|
||||
import Data.Bits(testBit,setBit)
|
||||
import Control.Applicative ((<$>),Applicative(..))
|
||||
import Control.Monad(liftM,ap)
|
||||
import qualified Data.Traversable as T (mapM)
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative ((<$>),Applicative(..))
|
||||
import Data.Traversable (mapM)
|
||||
import Prelude hiding (mapM)
|
||||
#endif
|
||||
|
||||
parse :: Config -> ParseM a -> String -> Either ParseError a
|
||||
parse cfg p cs = case unP p cfg eofPos (S toks) of
|
||||
@ -220,8 +224,8 @@ binOp x f y = at (x,y) $ EApp (EApp f x) y
|
||||
|
||||
eFromTo :: Range -> Expr -> Maybe Expr -> Maybe Expr -> ParseM Expr
|
||||
eFromTo r e1 e2 e3 = EFromTo <$> exprToNumT r e1
|
||||
<*> T.mapM (exprToNumT r) e2
|
||||
<*> T.mapM (exprToNumT r) e3
|
||||
<*> mapM (exprToNumT r) e2
|
||||
<*> mapM (exprToNumT r) e3
|
||||
exprToNumT :: Range -> Expr -> ParseM Type
|
||||
exprToNumT r expr =
|
||||
case translateExprToNumT expr of
|
||||
|
@ -56,7 +56,6 @@ import Cryptol.Prims.Doc(helpDoc)
|
||||
import qualified Cryptol.Transform.Specialize as S
|
||||
import qualified Cryptol.Symbolic as Symbolic
|
||||
|
||||
import Control.Applicative ((<$>))
|
||||
import Control.DeepSeq
|
||||
import qualified Control.Exception as X
|
||||
import Control.Monad (guard,unless,forM_,when)
|
||||
@ -64,7 +63,7 @@ import Data.Char (isSpace,isPunctuation,isSymbol)
|
||||
import Data.Function (on)
|
||||
import Data.List (intercalate,isPrefixOf,nub)
|
||||
import Data.Maybe (fromMaybe,mapMaybe)
|
||||
import Data.Monoid (mempty)
|
||||
import System.Environment (lookupEnv)
|
||||
import System.Exit (ExitCode(ExitSuccess))
|
||||
import System.Process (shell,createProcess,waitForProcess)
|
||||
import qualified System.Process as Process(runCommand)
|
||||
@ -76,35 +75,9 @@ import System.IO(hFlush,stdout)
|
||||
import System.Random.TF(newTFGen)
|
||||
import Numeric (showFFloat)
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 706
|
||||
import Control.Monad (liftM)
|
||||
import qualified Text.ParserCombinators.ReadP as P
|
||||
import Text.Read hiding (step)
|
||||
import System.Environment (getEnvironment)
|
||||
|
||||
lookupEnv :: String -> IO (Maybe String)
|
||||
lookupEnv key = lookup key `liftM` getEnvironment
|
||||
|
||||
readEither :: Read a => String -> Either String a
|
||||
readEither s =
|
||||
case [ x | (x,"") <- readPrec_to_S read' minPrec s ] of
|
||||
[x] -> Right x
|
||||
[] -> Left "Prelude.read: no parse"
|
||||
_ -> Left "Prelude.read: ambiguous parse"
|
||||
where
|
||||
read' =
|
||||
do x <- readPrec
|
||||
lift P.skipSpaces
|
||||
return x
|
||||
|
||||
-- | Parse a string using the 'Read' instance.
|
||||
-- Succeeds if there is exactly one valid result.
|
||||
readMaybe :: Read a => String -> Maybe a
|
||||
readMaybe s = case readEither s of
|
||||
Left _ -> Nothing
|
||||
Right a -> Just a
|
||||
#else
|
||||
import System.Environment (lookupEnv)
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative ((<$>))
|
||||
import Data.Monoid (mempty)
|
||||
#endif
|
||||
|
||||
-- Commands --------------------------------------------------------------------
|
||||
|
@ -82,13 +82,11 @@ import Cryptol.Utils.Panic (panic)
|
||||
import qualified Cryptol.Parser.AST as P
|
||||
import Cryptol.Symbolic (proverNames, lookupProver)
|
||||
|
||||
import Control.Applicative ((<$>), Applicative(..))
|
||||
import Control.Monad (ap,unless,when)
|
||||
import Data.IORef
|
||||
(IORef,newIORef,readIORef,modifyIORef)
|
||||
import Data.List (intercalate, isPrefixOf)
|
||||
import Data.Maybe (catMaybes)
|
||||
import Data.Monoid (Monoid(..))
|
||||
import Data.Typeable (Typeable)
|
||||
import System.Directory (findExecutable)
|
||||
import qualified Control.Exception as X
|
||||
@ -97,6 +95,10 @@ import Text.Read (readMaybe)
|
||||
|
||||
import Data.SBV.Dynamic (sbvCheckSolverInstallation)
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative ((<$>), Applicative(..))
|
||||
import Data.Monoid (Monoid(..))
|
||||
#endif
|
||||
|
||||
-- REPL Environment ------------------------------------------------------------
|
||||
|
||||
|
@ -12,14 +12,11 @@
|
||||
|
||||
module Cryptol.Symbolic where
|
||||
|
||||
import Control.Applicative
|
||||
import Control.Monad (replicateM, when, zipWithM)
|
||||
import Control.Monad.IO.Class
|
||||
import Data.List (transpose, intercalate)
|
||||
import qualified Data.Map as Map
|
||||
import Data.Maybe
|
||||
import Data.Monoid (Monoid(..))
|
||||
import Data.Traversable (traverse)
|
||||
import qualified Control.Exception as X
|
||||
|
||||
import qualified Data.SBV.Dynamic as SBV
|
||||
@ -38,6 +35,12 @@ import Cryptol.TypeCheck.Solver.InfNat (Nat'(..))
|
||||
import Cryptol.Utils.PP
|
||||
import Cryptol.Utils.Panic(panic)
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative
|
||||
import Data.Monoid (Monoid(..))
|
||||
import Data.Traversable (traverse)
|
||||
#endif
|
||||
|
||||
-- External interface ----------------------------------------------------------
|
||||
|
||||
proverConfigs :: [(String, SBV.SMTConfig)]
|
||||
|
@ -11,7 +11,7 @@
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
module Cryptol.Symbolic.Prims where
|
||||
|
||||
import Control.Applicative
|
||||
import Data.Bits
|
||||
import Data.List (genericDrop, genericReplicate, genericSplitAt, genericTake, sortBy, transpose)
|
||||
import Data.Ord (comparing)
|
||||
|
||||
@ -25,6 +25,10 @@ import Cryptol.Utils.Panic
|
||||
|
||||
import qualified Data.SBV.Dynamic as SBV
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative
|
||||
#endif
|
||||
|
||||
traverseSnd :: Functor f => (a -> f b) -> (t, a) -> f (t, b)
|
||||
traverseSnd f (x, y) = (,) x <$> f y
|
||||
|
||||
|
@ -12,9 +12,12 @@ import qualified Cryptol.Testing.Eval as Eval
|
||||
import Cryptol.TypeCheck.AST
|
||||
import Cryptol.Eval.Value
|
||||
|
||||
import Control.Applicative((<$>))
|
||||
import Data.List(genericReplicate)
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative((<$>))
|
||||
#endif
|
||||
|
||||
{- | Given a (function) type, compute all possible inputs for it.
|
||||
We also return the total number of test (i.e., the length of the outer list. -}
|
||||
testableType :: Type -> Maybe (Integer, [[Value]])
|
||||
|
@ -79,12 +79,15 @@ module Cryptol.Transform.MonoValues (rewModule) where
|
||||
import Cryptol.Parser.AST (Pass(MonoValues))
|
||||
import Cryptol.TypeCheck.AST
|
||||
import Cryptol.TypeCheck.TypeMap
|
||||
import Control.Applicative
|
||||
import Data.List(sortBy,groupBy)
|
||||
import Data.Either(partitionEithers)
|
||||
import Data.Map (Map)
|
||||
import MonadLib
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative
|
||||
#endif
|
||||
|
||||
{- (f,t,n) |--> x means that when we spot instantiations of `f` with `ts` and
|
||||
`n` proof argument, we should replace them with `Var x` -}
|
||||
newtype RewMap' a = RM (Map QName (TypesMap (Map Int a)))
|
||||
|
@ -16,15 +16,17 @@ import qualified Cryptol.ModuleSystem as M
|
||||
import qualified Cryptol.ModuleSystem.Env as M
|
||||
import qualified Cryptol.ModuleSystem.Monad as M
|
||||
|
||||
import Control.Applicative
|
||||
import Data.List (intercalate)
|
||||
import Data.Map (Map)
|
||||
import qualified Data.Map as Map
|
||||
import Data.Maybe (catMaybes)
|
||||
import Data.Traversable (traverse)
|
||||
|
||||
import MonadLib
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative
|
||||
import Data.Traversable (traverse)
|
||||
#endif
|
||||
|
||||
-- Specializer Monad -----------------------------------------------------------
|
||||
|
||||
|
@ -35,7 +35,10 @@ import Data.Maybe(mapMaybe)
|
||||
import MonadLib
|
||||
import qualified Control.Applicative as A
|
||||
import Control.Monad.Fix(MonadFix(..))
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Data.Functor
|
||||
#endif
|
||||
|
||||
-- | Information needed for type inference.
|
||||
data InferInput = InferInput
|
||||
|
@ -6,7 +6,7 @@
|
||||
-- Stability : provisional
|
||||
-- Portability : portable
|
||||
|
||||
{-# LANGUAGE OverloadedStrings, RecordWildCards, PatternGuards, Trustworthy #-}
|
||||
{-# LANGUAGE OverloadedStrings, RecordWildCards, PatternGuards #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
module Cryptol.TypeCheck.Solver.Smtlib (simpDelayed) where
|
||||
|
||||
|
@ -15,11 +15,14 @@ import Cryptol.TypeCheck.AST
|
||||
import Cryptol.TypeCheck.Subst
|
||||
import Cryptol.Utils.Panic (panic)
|
||||
|
||||
import Control.Applicative (Applicative(..))
|
||||
import Data.Ord(comparing)
|
||||
import Data.List(sortBy)
|
||||
import qualified Data.Set as Set
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative (Applicative(..))
|
||||
#endif
|
||||
|
||||
-- | The most general unifier is a substitution and a set of constraints
|
||||
-- on bound variables.
|
||||
type MGU = (Subst,[Prop])
|
||||
|
@ -9,10 +9,9 @@
|
||||
|
||||
module Main where
|
||||
|
||||
import Control.Applicative ((<$>))
|
||||
import Control.Monad (when,unless,foldM)
|
||||
import Control.Monad (when,foldM)
|
||||
import Data.List (isPrefixOf,partition,nub)
|
||||
import Data.Monoid (Monoid(..),Endo(..))
|
||||
import Data.Monoid (Endo(..))
|
||||
import System.Console.GetOpt
|
||||
(getOpt,usageInfo,ArgOrder(..),OptDescr(..),ArgDescr(..))
|
||||
import System.Directory
|
||||
@ -27,14 +26,18 @@ import System.Process
|
||||
(createProcess,CreateProcess(..),StdStream(..),proc,waitForProcess
|
||||
,readProcessWithExitCode)
|
||||
import System.IO
|
||||
(hGetContents,IOMode(..),withFile,SeekMode(..),Handle,hSetBuffering
|
||||
,BufferMode(..))
|
||||
(IOMode(..),withFile,Handle,hSetBuffering,BufferMode(..))
|
||||
import Test.Framework (defaultMain,Test,testGroup)
|
||||
import Test.Framework.Providers.HUnit (testCase)
|
||||
import Test.HUnit (assertFailure)
|
||||
import qualified Control.Exception as X
|
||||
import qualified Data.Map as Map
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative ((<$>))
|
||||
import Data.Monoid (Monoid(..))
|
||||
#endif
|
||||
|
||||
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
|
||||
import Text.Regex
|
||||
#endif
|
||||
@ -179,7 +182,6 @@ generateAssertion opts dir file = testCase file $ do
|
||||
goldFile = dir </> file <.> "stdout"
|
||||
resultOut = resultDir </> file <.> "stdout"
|
||||
resultDir = optResultDir opts </> dir
|
||||
indent str = unlines (map (" " ++) (lines str))
|
||||
checkOutput mbKnown expected out
|
||||
| expected == out =
|
||||
case mbKnown of
|
||||
@ -196,8 +198,8 @@ generateAssertion opts dir file = testCase file $ do
|
||||
|
||||
| otherwise ->
|
||||
do goldFile' <- canonicalizePath goldFile
|
||||
(_,out,_) <- readProcessWithExitCode "diff" [ goldFile', resultOut ] ""
|
||||
assertFailure out
|
||||
(_,diffOut,_) <- readProcessWithExitCode "diff" [ goldFile', resultOut ] ""
|
||||
assertFailure diffOut
|
||||
|
||||
Right fail_msg -> assertFailure fail_msg
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user