From b2e16029edf1b98a6673b593f18f82c5f1314c46 Mon Sep 17 00:00:00 2001
From: Matt Walker <matt.g.d.walker@gmail.com>
Date: Tue, 27 Feb 2024 23:44:01 -0500
Subject: [PATCH] falsify => QuickCheck
---
flake.nix | 1 +
ghc-pbts.cabal | 3 +-
tests/Main.hs | 14 +++--
tests/Pbt/Driver.hs | 22 +++++---
tests/Pbt/Expr.hs | 76 +++++++++++++------------
tests/Pbt/Expr/Utility.hs | 18 +++++-
tests/Pbt/Properties.hs | 116 +++++++++++++++-----------------------
7 files changed, 126 insertions(+), 124 deletions(-)
diff --git a/flake.nix b/flake.nix
index 34975a1..295fe62 100644
--- a/flake.nix
+++ b/flake.nix
@@ -30,6 +30,7 @@
haskell-language-server
ghcid
cabal-install
+ haskell-debug-adapter
];
});
};
diff --git a/ghc-pbts.cabal b/ghc-pbts.cabal
index 2b8f125..ee974c3 100644
--- a/ghc-pbts.cabal
+++ b/ghc-pbts.cabal
@@ -24,13 +24,14 @@ extra-source-files: CHANGELOG.md
test-suite ghc-pbts
type: exitcode-stdio-1.0
build-depends: base,
- falsify,
mtl,
process,
filepath,
temporary,
data-default,
tasty,
+ tasty-quickcheck,
+ QuickCheck,
text,
main-is: Main.hs
diff --git a/tests/Main.hs b/tests/Main.hs
index c4592e9..2f3657b 100644
--- a/tests/Main.hs
+++ b/tests/Main.hs
@@ -1,25 +1,29 @@
{-# LANGUAGE ImportQualifiedPost #-}
+{-# LANGUAGE TypeApplications #-}
module Main where
import Pbt.Properties qualified as Pbt
import Control.Monad (replicateM)
+import Data.Proxy (Proxy (..))
import Pbt.Driver (DriverState (..))
+import Pbt.Expr (genApp, genExpr, genLit, genVar)
import Pbt.Expr.Utility (betaReduce, utility1)
-import Test.Falsify.Interactive (falsify, sample)
+import Pbt.Properties (genDefaultInt, genPalka, outputsMatch)
import Test.Tasty (
defaultIngredients,
defaultMainWithIngredients,
testGroup,
)
-import Test.Tasty.Falsify (testProperty)
+import Test.Tasty.QuickCheck
main :: IO ()
main = do
defaultMainWithIngredients defaultIngredients $
testGroup
"PBTs"
- [ -- testProperty "palka" Pbt.palka
- testProperty "outputsMatch" Pbt.defaultOutputsMatch
- ]
+ [testProperty "default" $ outputsMatch genDefaultInt]
+
+-- testProperty "palka" Pbt.palka
+-- testProperty "outputsMatch" Pbt.defaultOutputsMatch
diff --git a/tests/Pbt/Driver.hs b/tests/Pbt/Driver.hs
index 7067eeb..9ec9b14 100644
--- a/tests/Pbt/Driver.hs
+++ b/tests/Pbt/Driver.hs
@@ -2,6 +2,7 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-cse -fno-full-laziness #-}
@@ -13,6 +14,8 @@ module Pbt.Driver (
makeModuleText,
writeModuleFile,
unsafeRunDriver,
+ shrinkDriverVia,
+ moduleDance,
genDriver,
) where
@@ -24,15 +27,14 @@ import Data.Text (Text)
import Data.Text qualified as Text
import Data.Text.IO qualified as Text
import Pbt.Expr qualified as Pbt
+import Pbt.Expr.Utility (shrinkExprVia)
import System.Exit (ExitCode (..))
import System.FilePath ((</>))
import System.IO (IOMode (WriteMode), hClose, withBinaryFile)
import System.IO.Temp qualified as Temp
import System.IO.Unsafe (unsafeDupablePerformIO)
import System.Process qualified as Process
-import Test.Falsify.Generator (list)
-import Test.Falsify.Range (between)
-import Test.Tasty.Falsify (Gen)
+import Test.QuickCheck.Gen (Gen)
import Type.Reflection (TypeRep (..), Typeable, typeRep)
data Import = Import
@@ -55,7 +57,6 @@ data DriverState ty = DriverState
, goldenFilename :: !Text
, optimizedFilename :: !Text
}
- deriving (Show)
newtype Driver ty a = Driver {unDriver :: StateT (DriverState ty) Identity a}
deriving newtype (Functor, Applicative, Monad, MonadState (DriverState ty))
@@ -158,7 +159,7 @@ runFileSimple fp = do
moduleDance :: (Show ty, Typeable ty) => DriverState ty -> IO ((Text, Text), (Text, Text))
moduleDance s = do
- Temp.withTempDirectory "." "ghc-pbts" $ \tempDirectory -> do
+ Temp.withSystemTempDirectory "ghc-pbts" $ \tempDirectory -> do
moduleDance'
tempDirectory
( s
@@ -185,11 +186,11 @@ unsafeRunDriver s = unsafeDupablePerformIO $ moduleDance s
genDriver :: Text -> [Pbt.SomeScopedId] -> Gen (Pbt.Expr ty) -> Gen (DriverState ty)
genDriver showExpr functions gExpr = do
- examples <- pure <$> gExpr
+ examples <- gExpr
pure $
DriverState
{ functions = functions
- , expressions = examples
+ , expressions = [examples]
, showExpression = showExpr
, goldenModuleName = "Main"
, optimizedModuleName = "Main"
@@ -200,3 +201,10 @@ genDriver showExpr functions gExpr = do
, goldenFilename = "M.hs"
, optimizedFilename = "M.hs"
}
+
+shrinkDriverVia :: (Show ty) => (forall a. (Show a) => Pbt.Expr a -> Maybe (Pbt.Expr a)) -> DriverState ty -> [DriverState ty]
+shrinkDriverVia exprShrinker s =
+ let exprs = expressions s
+ exprToDriver e = s{expressions = [e]}
+ shrunkExprs = shrinkExprVia exprShrinker =<< exprs
+ in exprToDriver <$> shrunkExprs
\ No newline at end of file
diff --git a/tests/Pbt/Expr.hs b/tests/Pbt/Expr.hs
index 5dfcc4a..1c4baae 100644
--- a/tests/Pbt/Expr.hs
+++ b/tests/Pbt/Expr.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ExplicitNamespaces #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
@@ -23,6 +24,9 @@ module Pbt.Expr (
GenExprWithContext (..),
Context (..),
genExpr,
+ genLit,
+ genVar,
+ genApp,
interpretToHsSrc,
interpretToHsSrc',
pattern (:-->),
@@ -41,12 +45,8 @@ import Data.Text (Text, pack)
import Data.Text qualified as Text
import Data.Text.IO qualified as Text
import Data.Traversable (fmapDefault, foldMapDefault)
-import Test.Falsify.GenDefault (GenDefault (genDefault))
-import Test.Falsify.GenDefault.Std (Std)
-import Test.Falsify.Generator (frequency, int, list, oneof)
-import Test.Falsify.Interactive (sample)
-import Test.Falsify.Range (between)
-import Test.Tasty.Falsify (Gen)
+import Test.QuickCheck (Arbitrary (arbitrary))
+import Test.QuickCheck.Gen (Gen, chooseInt, frequency, vectorOf)
import Type.Reflection (TypeRep, Typeable, eqTypeRep, someTypeRep, typeRep, type (:~~:) (..))
instance Show (a -> b) where
@@ -115,7 +115,7 @@ data SomeScopedId = forall a. (Typeable a) => SomeScopedId (ScopedId a)
instance Show SomeScopedId where
show (SomeScopedId si) = show si
-data SomeTypeProxy tag = forall a. (Show a, Typeable a, GenExprWithContext tag a) => SomeTypeProxy (Proxy a)
+data SomeTypeProxy = forall a. (Show a, Typeable a, GenExprWithContext a) => SomeTypeProxy (Proxy a)
interpretToHsSrc :: (Show a) => Expr a -> Text
interpretToHsSrc (Var (Id ident isInfix)) = "(" <> ident <> ")"
@@ -131,31 +131,31 @@ instance (Show ty) => Show (Expr ty) where
type Size = Word
-data Context tag = Context
+data Context = Context
{ size :: !Size
- , inScopeIds :: [(Word, SomeScopedId)]
- , genTypeProxy :: Gen (SomeTypeProxy tag)
- , newLambdaFreq :: Size -> Word
- , newLocalVarFreq :: Int {-- length of the identifier list --} -> Size -> Word
- , newAppFreq :: Size -> Word
- , newVarFreq :: Size -> Word
- , newLitFreq :: Size -> Word
+ , inScopeIds :: [(Int, SomeScopedId)]
+ , genTypeProxy :: Gen SomeTypeProxy
+ , newLambdaFreq :: Size -> Int
+ , newLocalVarFreq :: Int {-- length of the identifier list --} -> Size -> Int
+ , newAppFreq :: Size -> Int
+ , newVarFreq :: Size -> Int
+ , newLitFreq :: Size -> Int
, newSize :: Size -> Size
}
-filterIds :: (Typeable a) => TypeRep a -> [(Word, SomeScopedId)] -> [(Word, ScopedId a)]
+filterIds :: (Typeable a) => TypeRep a -> [(Int, SomeScopedId)] -> [(Int, ScopedId a)]
filterIds x someIds = filterIds' x someIds []
where
- filterIds' :: (Typeable a) => TypeRep a -> [(Word, SomeScopedId)] -> [(Word, ScopedId a)] -> [(Word, ScopedId a)]
- filterIds' x [] acc = acc
- filterIds' x ((w, SomeScopedId (y :: ScopedId b)) : ys) acc =
+ filterIds' :: (Typeable a) => TypeRep a -> [(Int, SomeScopedId)] -> [(Int, ScopedId a)] -> [(Int, ScopedId a)]
+ filterIds' x [] !acc = acc
+ filterIds' x ((w, SomeScopedId (y :: ScopedId b)) : ys) !acc =
case eqTypeRep x (typeRep @b) of
Just HRefl ->
filterIds' x ys ((w, y) : acc)
Nothing ->
filterIds' x ys acc
-genExpr :: (Show a, Typeable a, GenExprWithContext tag a) => Context tag -> Gen (Expr a)
+genExpr :: (Show a, Typeable a, GenExprWithContext a) => Context -> Gen (Expr a)
genExpr ctx =
frequency
[ (newAppFreq ctx (size ctx), genApp ctx')
@@ -165,23 +165,23 @@ genExpr ctx =
where
ctx' = ctx{size = newSize ctx (size ctx)}
-genFreshishId :: (Typeable a) => Proxy a -> Context tag -> Gen (Id a)
+genFreshishId :: (Typeable a) => Proxy a -> Context -> Gen (Id a)
genFreshishId pxy ctx = do
-- FIXME: Sometimes breaks if you pick the same int more than once and the types don't match!
- i <- int $ between (0, 1000000)
+ i <- chooseInt (0, 1000000)
let typeName = someTypeRep pxy & show & Text.pack
pure . (`Id` False) $ "x" <> Text.pack (show i)
-genVar :: (Show a, Typeable a, GenExprWithContext tag a) => Proxy a -> Context tag -> Gen (Expr a)
+genVar :: (Show a, Typeable a, GenExprWithContext a) => Proxy a -> Context -> Gen (Expr a)
genVar (pxy :: Proxy a) ctx =
frequency $
-- This erases the isInfix info
(1, genLit ctx) : (fmap (pure . Var . (`Id` False) . localName) <$> filterIds (typeRep @a) (inScopeIds ctx))
-genLit :: (Typeable a, Show a, GenExprWithContext tag a) => Context tag -> Gen (Expr a)
-genLit (ctx :: Context tag) = genExprWithContext ctx
+genLit :: (Typeable a, Show a, GenExprWithContext a) => Context -> Gen (Expr a)
+genLit = genExprWithContext
-genApp :: (Show a, Typeable a, GenExprWithContext tag a) => Context tag -> Gen (Expr a)
+genApp :: (Show a, Typeable a, GenExprWithContext a) => Context -> Gen (Expr a)
genApp ctx = do
SomeTypeProxy (pxy :: Proxy b) <- genTypeProxy ctx
newLambda :: Expr (b -> a) <- genExprWithContext ctx
@@ -194,16 +194,16 @@ genApp ctx = do
pure $ App fun appBody
_ -> error "impossible: `genExprWithContext @tag @(b -> a)` generated a non-lambda."
-instance GenDefault Std (Expr Int) where
- genDefault _ = Lit <$> genDefault (Proxy @Std)
+instance Arbitrary (Expr Int) where
+ arbitrary = Lit <$> arbitrary
-class GenExprWithContext tag a where
- genExprWithContext :: Context tag -> Gen (Expr a)
+class GenExprWithContext a where
+ genExprWithContext :: Context -> Gen (Expr a)
-instance GenExprWithContext Std () where
+instance GenExprWithContext () where
genExprWithContext _ = pure $ Lit ()
-instance GenExprWithContext Std Double where
+instance GenExprWithContext Double where
genExprWithContext _ =
fmap Lit . (*)
<$> frequency
@@ -226,13 +226,15 @@ instance GenExprWithContext Std Double where
]
)
-instance GenExprWithContext Std Int where
- genExprWithContext _ = genDefault (Proxy @Std)
+instance GenExprWithContext Int where
+ genExprWithContext _ = arbitrary
-instance GenExprWithContext Std [Int] where
- genExprWithContext ctx = Lit <$> list (between (0, size ctx)) (int (between (0, fromIntegral (size ctx))))
+instance GenExprWithContext [Int] where
+ genExprWithContext ctx = do
+ n <- chooseInt (0, fromIntegral $ size ctx)
+ Lit <$> vectorOf n (chooseInt (0, fromIntegral (size ctx)))
-instance (Typeable b, Show b, Typeable a, Show a, GenExprWithContext t a) => GenExprWithContext t (b -> a) where
+instance (Typeable b, Show b, Typeable a, Show a, GenExprWithContext a) => GenExprWithContext (b -> a) where
genExprWithContext ctx = do
freshishId <- genFreshishId Proxy ctx
let ctx' = ctx{inScopeIds = (newLocalVarFreq ctx (fromIntegral (length (inScopeIds ctx))) (size ctx), SomeScopedId (LocalId freshishId)) : inScopeIds ctx}
diff --git a/tests/Pbt/Expr/Utility.hs b/tests/Pbt/Expr/Utility.hs
index dda7219..c66e76e 100644
--- a/tests/Pbt/Expr/Utility.hs
+++ b/tests/Pbt/Expr/Utility.hs
@@ -3,12 +3,14 @@
{-# LANGUAGE GADTs #-}
-- OverloadedStrings required for doctests
{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
module Pbt.Expr.Utility where
+import Data.Maybe (fromMaybe, maybeToList)
import Pbt.Expr (
Binder (..),
Context (..),
@@ -17,8 +19,9 @@ import Pbt.Expr (
Size,
SomeScopedId,
SomeTypeProxy,
+ interpretToHsSrc,
)
-import Test.Falsify.Generator (Gen)
+import Test.QuickCheck.Gen (Gen)
import Type.Reflection (
Typeable,
eqTypeRep,
@@ -139,6 +142,15 @@ betaReduce (App f x) =
betaReduce (Lam binder body) = Lam binder (betaReduce body)
betaReduce e = e
+isBetaReduced :: (Show a) => Expr a -> Bool
+isBetaReduced e = interpretToHsSrc e == interpretToHsSrc (betaReduce e)
+
+tryBetaReduce :: (Show a) => Expr a -> Maybe (Expr a)
+tryBetaReduce e = if isBetaReduced e then Nothing else Just (betaReduce e)
+
+shrinkExprVia :: (Show a) => (forall ty. (Show ty) => Expr ty -> Maybe (Expr ty)) -> Expr a -> [Expr a]
+shrinkExprVia s e = maybeToList (s e)
+
utility1 :: Expr a -> Double
utility1 e =
if reducesToLiteral e
@@ -147,8 +159,8 @@ utility1 e =
fromIntegral (countUsedLocalVars e * countConstants e * maxFunctionDepth (betaReduce e))
/ fromIntegral (1 + countIdentityFunctions e * countConstantFunctions e * maxFunctionDepth e)
-mkContext1 :: (Size, [SomeScopedId], Gen (SomeTypeProxy tag), Size) -> (Word, Word, Word, Word, Word, Word) -> Context tag
+mkContext1 :: (Size, [SomeScopedId], Gen SomeTypeProxy, Size) -> (Int, Int, Int, Int, Int, Int) -> Context
mkContext1 (size, scopedIds, genTypeProxy, sizeDivider) (scopedIdFreq, lamFreq, localVarFreq, appFreq, varFreq, litFreq) =
- Context size inScopeIds genTypeProxy (\x -> x * lamFreq + 1) (fmap (+ 1) . (*) . (* localVarFreq) . fromIntegral) (\x -> x * appFreq + 1) (\x -> x * varFreq + 1) (\x -> x * litFreq + 1) (`div` sizeDivider)
+ Context size inScopeIds genTypeProxy (\x -> fromIntegral x * lamFreq + 1) (\x y -> fromIntegral y * localVarFreq + 1) (\x -> fromIntegral x * appFreq + 1) (\x -> fromIntegral x * varFreq + 1) (\x -> fromIntegral x * litFreq + 1) (`div` sizeDivider)
where
inScopeIds = fmap (scopedIdFreq,) scopedIds
diff --git a/tests/Pbt/Properties.hs b/tests/Pbt/Properties.hs
index a9b26ee..cd3060d 100644
--- a/tests/Pbt/Properties.hs
+++ b/tests/Pbt/Properties.hs
@@ -3,14 +3,30 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
-module Pbt.Properties (outputsMatch, defaultOutputsMatch, genPalka, palka, guardBy) where
-
-import Control.Monad (replicateM)
+module Pbt.Properties (
+ outputsMatch,
+ genPalka,
+ genDefaultInt,
+ simpleContext,
+ guardBy,
+) where
+
+import Control.Monad (replicateM, when)
import Data.Proxy (Proxy (..))
-import Data.Text (Text, unpack)
+import Data.Text (Text)
+import Data.Text qualified as Text
import Data.Text.IO qualified as Text
import Debug.Trace (traceM)
-import Pbt.Driver (Driver (..), DriverState (..), genDriver, makeModuleText, unsafeRunDriver, writeModuleFile)
+import Pbt.Driver (
+ Driver (..),
+ DriverState (..),
+ genDriver,
+ makeModuleText,
+ moduleDance,
+ shrinkDriverVia,
+ unsafeRunDriver,
+ writeModuleFile,
+ )
import Pbt.Expr (
Context (..),
Expr,
@@ -21,15 +37,12 @@ import Pbt.Expr (
genExpr,
interpretToHsSrc,
)
-import Pbt.Expr.Utility (betaReduce, mkContext1, utility1)
-import Test.Falsify.GenDefault.Std (Std)
-import Test.Falsify.Generator (Gen, frequency)
-import Test.Falsify.Interactive (sample)
-import Test.Falsify.Predicate (eq, (.$))
-import Test.Tasty.Falsify (Property, assert, gen, info)
+import Pbt.Expr.Utility (betaReduce, mkContext1, tryBetaReduce, utility1)
+import Test.QuickCheck.Gen (Gen, frequency)
+import Test.QuickCheck.Property (Property, forAll, forAllShrinkBlind, forAllShrinkShow, ioProperty)
import Type.Reflection (Typeable)
-genTypeProxy1 :: Gen (SomeTypeProxy Std)
+genTypeProxy1 :: Gen SomeTypeProxy
genTypeProxy1 =
frequency
[ (1, pure $ SomeTypeProxy (Proxy @()))
@@ -39,7 +52,7 @@ genTypeProxy1 =
, (8, pure $ SomeTypeProxy (Proxy @((Int -> Int) -> Int -> Int)))
]
-genTypeProxy2 :: Gen (SomeTypeProxy Std)
+genTypeProxy2 :: Gen SomeTypeProxy
genTypeProxy2 =
frequency
[ (8, pure $ SomeTypeProxy (Proxy @Int))
@@ -48,7 +61,7 @@ genTypeProxy2 =
, (8, pure $ SomeTypeProxy (Proxy @([Int] -> [Int])))
]
-genTypeProxyPalka :: Gen (SomeTypeProxy Std)
+genTypeProxyPalka :: Gen SomeTypeProxy
genTypeProxyPalka =
frequency
[ (4, pure $ SomeTypeProxy (Proxy @Int))
@@ -187,69 +200,30 @@ functions2 =
[ SomeScopedId cons
]
-main :: IO ()
-main = do
- let mkVariableContext = mkContext1 (100, functions2, genTypeProxy2, 2)
- let initVariables = (1000, 250, 1000, 2000, 25, 25)
- -- Context
- -- { size = 100
- -- , inScopeIds = (4,) <$> functions
- -- , genTypeProxy = genTypeProxy2
- -- , newLambdaFreq = const 8
- -- , newLocalVarFreq = \len _ -> fromIntegral len
- -- , newAppFreq = \x -> 4 * x + 1
- -- , newVarFreq = \x -> 4 * x + 1
- -- , newLitFreq = (+ 1)
- -- , newSize = (`div` 2)
- -- }
- examples :: [Expr [Int]] <-
- replicateM
- 100
- ( sample
- (guardBy (\x -> utility1 x /= 0) $ genExpr @_ @Std (mkVariableContext initVariables))
- )
- -- let betaReducedExamples = betaReduce <$> examples
- let s =
- DriverState
- { functions = functions2
- , expressions = take 100 examples
- , showExpression = "id"
- , goldenModuleName = "Main"
- , optimizedModuleName = "Main"
- , languagePragmas = []
- , moduleImports = []
- , goldenOptionsGhc = []
- , optimizedOptionsGhc = ["-O2"]
- , goldenFilename = "M.hs"
- , optimizedFilename = "Mopt.hs"
- }
- if uncurry (==) (unsafeRunDriver s) then putStrLn "Ok!" else putStrLn "Bad!"
- putStrLn ("Average utility was: " <> show (averageBy utility1 examples))
-
-outputsMatch :: (Typeable ty, Show ty) => DriverState ty -> Property ()
-outputsMatch s = do
- let (g, o) = unsafeRunDriver s
- info $ "Average utility was: " <> show (averageBy utility1 (expressions s))
- assert $
- eq
- .$ ("golden", g)
- .$ ("optimized", o)
+outputsMatch :: (Typeable ty, Show ty) => Gen (DriverState ty) -> Property
+outputsMatch s =
+ forAllShrinkShow
+ s
+ (shrinkDriverVia tryBetaReduce)
+ (Text.unpack . Text.concat . fmap interpretToHsSrc . expressions)
+ $ \s' -> ioProperty $ do
+ (g, o) <- moduleDance s'
+ pure (g == o)
genPalka :: Gen (DriverState ([Int] -> [Int]))
genPalka =
let mkVariableContext = mkContext1 (100, functionsPalka, genTypeProxyPalka, 2)
initVariables = (1000, 250, 1000, 2000, 25, 25)
- in genDriver "($ ((1 :: Int) : 2 : undefined))" functionsPalka (genExpr @([Int] -> [Int]) @Std (mkVariableContext initVariables))
+ in genDriver "($ ((1 :: Int) : 2 : undefined))" functionsPalka (genExpr @([Int] -> [Int]) (mkVariableContext initVariables))
-palka :: Property ()
-palka = do
- d <- gen genPalka
- outputsMatch d
+simpleContext :: Context
+simpleContext =
+ let mkVariableContext = mkContext1 (100, functions1, genTypeProxy1, 2)
+ initVariables = (1000, 250, 1000, 2000, 25, 25)
+ in mkVariableContext initVariables
-defaultOutputsMatch :: Property ()
-defaultOutputsMatch = do
+genDefaultInt :: Gen (DriverState Int)
+genDefaultInt = do
let mkVariableContext = mkContext1 (100, functions1, genTypeProxy1, 2)
let initVariables = (1000, 250, 1000, 2000, 25, 25)
- d <- gen $ genDriver "id" functions1 (genExpr @Int @Std (mkVariableContext initVariables))
- traceM $ unpack $ makeModuleText True d
- outputsMatch d
\ No newline at end of file
+ genDriver "id" functions1 (genExpr @Int (mkVariableContext initVariables))
--
GitLab