Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
3 changes: 2 additions & 1 deletion plutus-core/executables/traceToStacks/TestGetStacks.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}

import Common
import System.Environment.IgnoreAccept
import Test.Tasty (defaultMain, testGroup)
import Test.Tasty.HUnit (testCase, (@?=))

Expand Down Expand Up @@ -76,7 +77,7 @@ kInyzInxStackVals = [
]

main :: IO ()
main = defaultMain $ testGroup "getStacks tests" [
main = ignoreAcceptOption $ defaultMain $ testGroup "getStacks tests" [
testCase "x only" (getStacks xEvent @?= xStackVal),
testCase "x calls y calling z" (getStacks zInyInxEvent @?= zInyInxStackVals),
testCase "x calls y and z" (getStacks yzInxEvent @?= yzInxStackVals),
Expand Down
3 changes: 2 additions & 1 deletion plutus-core/flat/test/Big.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ import PlutusCore.Flat (Decoded, Flat (..), flat, unflat, unflatWith)
import PlutusCore.Flat.AsBin (AsBin, unbin)
import PlutusCore.Flat.AsSize
import PlutusCore.Flat.Decoder (Get, listTDecoder)
import System.Environment.IgnoreAccept
import System.TimeIt (timeIt)

-- Big is a type that has a small encoded representation but a very large in-memory footprint.
Expand Down Expand Up @@ -42,7 +43,7 @@ instance Flat Big where
decode = newBig <$> decode

main :: IO ()
main = tbig
main = ignoreAcceptOption tbig

tbig = do
let numOfBigs = 5
Expand Down
7 changes: 2 additions & 5 deletions plutus-core/flat/test/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,7 @@ import PlutusCore.Flat.Encoder qualified as E
import PlutusCore.Flat.Encoder.Prim qualified as E
import PlutusCore.Flat.Encoder.Strict qualified as E
import PlutusCore.Flat.Endian
import System.Environment.IgnoreAccept
import System.Exit
import Test.Data
import Test.Data.Arbitrary ()
Expand Down Expand Up @@ -87,7 +88,7 @@ mainShow = do
mapM_ (\_ -> generate (arbitrary :: Gen Int) >>= print) [1 .. 10]
exitFailure

mainTest = defaultMain tests
mainTest = ignoreAcceptOption $ defaultMain tests

tests :: TestTree
tests = testGroup "Tests" [testPrimitives, testEncDec, testFlat]
Expand Down Expand Up @@ -794,7 +795,3 @@ prop_common_unsigned n _ = let n2 :: h = fromIntegral n
-- b1 :: BLOB UTF8
-- b1 = BLOB UTF8 (preAligned (List255 [97,98,99]))
-- -- b1 = BLOB (preAligned (UTF8 (List255 [97,98,99])))




3 changes: 2 additions & 1 deletion plutus-core/index-envs/test/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,8 @@ module Main
) where

import RAList.Spec qualified as RAList
import System.Environment.IgnoreAccept
import Test.Tasty

main :: IO ()
main = defaultMain RAList.tests
main = ignoreAcceptOption $ defaultMain RAList.tests
10 changes: 8 additions & 2 deletions plutus-core/plutus-core.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -811,6 +811,7 @@ library plutus-core-testlib
PlutusIR.Generators.QuickCheck.ShrinkTerms
PlutusIR.Pass.Test
PlutusIR.Test
System.Environment.IgnoreAccept
Test.Tasty.Extras
UntypedPlutusCore.Generators.Hedgehog.AST
UntypedPlutusCore.Test.DeBruijn.Bad
Expand Down Expand Up @@ -905,6 +906,7 @@ test-suite traceToStacks-test
, base >=4.9 && <5
, bytestring
, cassava
, plutus-core:plutus-core-testlib
, tasty
, tasty-hunit
, text
Expand Down Expand Up @@ -1080,6 +1082,7 @@ test-suite satint-test
, base >=4.9 && <5
, HUnit
, QuickCheck
, plutus-core:plutus-core-testlib
, satint
, test-framework
, test-framework-hunit
Expand Down Expand Up @@ -1136,9 +1139,10 @@ test-suite index-envs-test
ghc-options: -threaded -rtsopts -with-rtsopts=-N
build-depends:
, base >=4.9 && <5
, QuickCheck
, index-envs
, nonempty-vector
, QuickCheck
, plutus-core:plutus-core-testlib
, quickcheck-instances
, tasty
, tasty-quickcheck
Expand Down Expand Up @@ -1241,11 +1245,12 @@ test-suite flat-test

build-depends:
, base
, QuickCheck
, bytestring
, containers
, deepseq
, plutus-core:flat
, QuickCheck
, plutus-core:plutus-core-testlib
, quickcheck-text
, tasty
, tasty-hunit
Expand All @@ -1268,4 +1273,5 @@ test-suite flat-big-test
, bytestring
, list-t
, plutus-core:flat
, plutus-core:plutus-core-testlib
, timeit
3 changes: 2 additions & 1 deletion plutus-core/satint/test/TestSatInt.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@
-- in safeint, since I want to upstream this in due course.
module Main where

import System.Environment.IgnoreAccept
import Control.Exception as E
import Data.List
import Data.Maybe
Expand All @@ -17,7 +18,7 @@ import Test.HUnit as T
import Test.QuickCheck

main :: IO ()
main = defaultMain tests
main = ignoreAcceptOption $ defaultMain tests

isArithException :: a -> IO Bool
isArithException n = E.catch (n `seq` return False)
Expand Down
10 changes: 10 additions & 0 deletions plutus-core/testlib/System/Environment/IgnoreAccept.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
module System.Environment.IgnoreAccept (ignoreAcceptOption) where

import System.Environment
import Data.List

-- | Ignores options like --accept and --accept=True from argv
ignoreAcceptOption :: IO a -> IO a
ignoreAcceptOption m = do
args <- getArgs
withArgs (filter (not . isPrefixOf "--accept") args) m