aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorYann Herklotz <git@yannherklotz.com>2020-04-07 01:31:45 +0100
committerYann Herklotz <git@yannherklotz.com>2020-04-07 01:31:45 +0100
commit39dfa92affb1271dc6f714dfca0e13ba72e72e24 (patch)
treec5e2472eeae15c47ab6ad9ee3783d1e81a7d93b4
parent2b00c249a29236af734c1e5b717b859a2a54a5dc (diff)
downloadverismith-39dfa92affb1271dc6f714dfca0e13ba72e72e24.tar.gz
verismith-39dfa92affb1271dc6f714dfca0e13ba72e72e24.zip
Add annotations and make it compile again
-rw-r--r--src/Verismith.hs8
-rw-r--r--src/Verismith/Fuzz.hs10
-rw-r--r--src/Verismith/OptParser.hs10
-rw-r--r--src/Verismith/Reduce.hs16
-rw-r--r--src/Verismith/Tool/Identity.hs4
-rw-r--r--src/Verismith/Tool/Quartus.hs4
-rw-r--r--src/Verismith/Tool/QuartusLight.hs4
-rw-r--r--src/Verismith/Tool/Vivado.hs4
-rw-r--r--src/Verismith/Tool/XST.hs4
-rw-r--r--src/Verismith/Tool/Yosys.hs4
-rw-r--r--src/Verismith/Verilog/AST.hs4
11 files changed, 41 insertions, 31 deletions
diff --git a/src/Verismith.hs b/src/Verismith.hs
index 3aa6d81..61a56f2 100644
--- a/src/Verismith.hs
+++ b/src/Verismith.hs
@@ -98,7 +98,7 @@ getConfig :: Maybe FilePath -> IO Config
getConfig s =
maybe (return defaultConfig) parseConfigFile $ T.unpack . toTextIgnore <$> s
-getGenerator :: Config -> Text -> Maybe FilePath -> IO (Gen (SourceInfo ann))
+getGenerator :: Config -> Text -> Maybe FilePath -> IO (Gen (SourceInfo ()))
getGenerator config top s =
maybe (return $ proceduralSrc top config) (fmap return . parseSourceInfoFile top)
$ toTextIgnore <$> s
@@ -183,7 +183,7 @@ handleOpts (Reduce f t _ ls' False) = do
shelly $ do
make dir
pop dir $ do
- src' <- reduceSynth Nothing (toFP datadir) a b src
+ src' <- reduceSynth Nothing (toFP datadir) a b src :: Sh (SourceInfo ())
writefile (fromText ".." </> dir <.> "v") $ genSource src'
a : _ -> do
putStrLn "Reduce with synthesis failure"
@@ -295,7 +295,7 @@ checkEquivalence src dir = shellyFailDir $ do
-- generated Verilog files are equivalent.
runEquivalence
:: Maybe Seed
- -> Gen Verilog -- ^ Generator for the Verilog file.
+ -> Gen (Verilog ()) -- ^ Generator for the Verilog file.
-> Text -- ^ Name of the folder on each thread.
-> Text -- ^ Name of the general folder being used.
-> Bool -- ^ Keep flag.
@@ -330,6 +330,6 @@ runEquivalence seed gm t d k i = do
when (i < 5 && isNothing seed) (runEquivalence seed gm t d k $ i + 1)
where n = t <> "_" <> T.pack (show i)
-runReduce :: (SourceInfo ann) -> IO (SourceInfo ann)
+runReduce :: (SourceInfo ()) -> IO (SourceInfo ())
runReduce s =
shelly $ reduce "reduce.v" (\s' -> not <$> liftIO (checkEquivalence s' "reduce")) s
diff --git a/src/Verismith/Fuzz.hs b/src/Verismith/Fuzz.hs
index 54104b6..10fbfa8 100644
--- a/src/Verismith/Fuzz.hs
+++ b/src/Verismith/Fuzz.hs
@@ -73,7 +73,7 @@ data FuzzOpts = FuzzOpts { _fuzzOptsOutput :: !(Maybe FilePath)
, _fuzzOptsNoEquiv :: !Bool
, _fuzzOptsNoReduction :: !Bool
, _fuzzOptsConfig :: {-# UNPACK #-} !Config
- , _fuzzDataDir :: {-# UNPACK #-} !FilePath
+ , _fuzzDataDir :: !FilePath
, _fuzzOptsCrossCheck :: !Bool
, _fuzzOptsChecker :: !(Maybe Text)
}
@@ -378,7 +378,7 @@ passEquiv = filter withIdentity . _fuzzSynthResults <$> get
withIdentity _ = False
-- | Always reduces with respect to 'Identity'.
-reduction :: (MonadSh m) => (SourceInfo ann) -> Fuzz m ()
+reduction :: (MonadSh m, Eq ann) => (SourceInfo ann) -> Fuzz m ()
reduction src = do
datadir <- fmap _fuzzDataDir askOpts
checker <- fmap _fuzzOptsChecker askOpts
@@ -465,7 +465,7 @@ medianFreqs l = zip hat (return <$> l)
hat = set_ <$> [1 .. length l]
set_ n = if n == h then 1 else 0
-fuzz :: MonadFuzz m => Gen (SourceInfo ann) -> Fuzz m FuzzReport
+fuzz :: (MonadFuzz m, Ord ann) => Gen (SourceInfo ann) -> Fuzz m FuzzReport
fuzz gen = do
conf <- askConfig
opts <- askOpts
@@ -507,7 +507,7 @@ fuzz gen = do
(getTime redResult)
return report
-fuzzInDir :: MonadFuzz m => Gen (SourceInfo ann) -> Fuzz m FuzzReport
+fuzzInDir :: (MonadFuzz m, Ord ann) => Gen (SourceInfo ann) -> Fuzz m FuzzReport
fuzzInDir src = do
fuzzOpts <- askOpts
let fp = fromMaybe "fuzz" $ _fuzzOptsOutput fuzzOpts
@@ -521,7 +521,7 @@ fuzzInDir src = do
bname = T.pack . takeBaseName . T.unpack . toTextIgnore
fuzzMultiple
- :: MonadFuzz m
+ :: (MonadFuzz m, Ord ann)
=> Gen (SourceInfo ann)
-> Fuzz m [FuzzReport]
fuzzMultiple src = do
diff --git a/src/Verismith/OptParser.hs b/src/Verismith/OptParser.hs
index 27ff4b4..592f9e9 100644
--- a/src/Verismith/OptParser.hs
+++ b/src/Verismith/OptParser.hs
@@ -24,7 +24,7 @@ instance Show OptTool where
show TXST = "xst"
show TIcarus = "icarus"
-data Opts = Fuzz { fuzzOutput :: {-# UNPACK #-} !Text
+data Opts = Fuzz { fuzzOutput :: Text
, fuzzConfigFile :: !(Maybe FilePath)
, fuzzForced :: !Bool
, fuzzKeepAll :: !Bool
@@ -40,13 +40,13 @@ data Opts = Fuzz { fuzzOutput :: {-# UNPACK #-} !Text
| Generate { generateFilename :: !(Maybe FilePath)
, generateConfigFile :: !(Maybe FilePath)
}
- | Parse { parseFilename :: {-# UNPACK #-} !FilePath
- , parseTop :: {-# UNPACK #-} !Text
+ | Parse { parseFilename :: !FilePath
+ , parseTop :: !Text
, parseOutput :: !(Maybe FilePath)
, parseRemoveConstInConcat :: !Bool
}
- | Reduce { reduceFilename :: {-# UNPACK #-} !FilePath
- , reduceTop :: {-# UNPACK #-} !Text
+ | Reduce { reduceFilename :: !FilePath
+ , reduceTop :: !Text
, reduceScript :: !(Maybe FilePath)
, reduceSynthesiserDesc :: ![SynthDescription]
, reduceRerun :: !Bool
diff --git a/src/Verismith/Reduce.hs b/src/Verismith/Reduce.hs
index 1ee36a6..3ea25a2 100644
--- a/src/Verismith/Reduce.hs
+++ b/src/Verismith/Reduce.hs
@@ -133,9 +133,15 @@ halveNonEmpty l = case NonEmpty.splitAt (length l `div` 2) l of
-- | When given a Lens and a function that works on a lower replacement, it will
-- go down, apply the replacement, and return a replacement of the original
-- module.
-combine :: Functor f => ((b -> f b) -> a -> f a) -> Replace b -> Replace a
+combine :: (Monoid b) => Traversal' a b -> Replace b -> Replace a
combine l f i = modify <$> f (i ^. l) where modify res = i & l .~ res
+-- | When given a Lens and a function that works on a lower replacement, it will
+-- go down, apply the replacement, and return a replacement of the original
+-- module.
+combineL :: Lens' a b -> Replace b -> Replace a
+combineL l f i = modify <$> f (i ^. l) where modify res = i & l .~ res
+
-- | Deletes Id 'Expr' if they are not part of the current scope, and replaces
-- these by 0.
filterExpr :: [Identifier] -> Expr -> Expr
@@ -237,7 +243,7 @@ addMod m srcInfo = srcInfo & infoSrc . _Wrapped %~ (m :)
-- | Split a module declaration in half by trying to remove assign
-- statements. This is only done in the main module of the source.
halveAssigns :: Replace (SourceInfo ann)
-halveAssigns = combine mainModule halveModAssign
+halveAssigns = combineL mainModule halveModAssign
-- | Checks if a module item is needed in the module declaration.
relevantModItem :: (ModDecl ann) -> (ModItem ann) -> Bool
@@ -409,8 +415,7 @@ modItemBot t srcInfo | length modItemsNoDecl > 2 = False
halveStatements :: Identifier -> Replace (SourceInfo ann)
halveStatements t m =
- cleanSourceInfo t <$> combine (aModule t . modItems) halves m
- where halves = traverse halveAlways
+ cleanSourceInfo t <$> combine (aModule t . modItems) (traverse halveAlways) m
-- | Reduce expressions by splitting them in half and keeping the half that
-- succeeds.
@@ -639,7 +644,8 @@ runInTmp a = Shelly.withTmpDir $ (\f -> do
Shelly.cd dir
return r)
-reduceSimIc :: (Synthesiser a, MonadSh m, Eq ann) => Shelly.FilePath -> [ByteString] -> a -> (SourceInfo ann) -> m (SourceInfo ann)
+reduceSimIc :: (Synthesiser a, MonadSh m, Eq ann) => Shelly.FilePath -> [ByteString]
+ -> a -> (SourceInfo ann) -> m (SourceInfo ann)
reduceSimIc fp bs a = reduce (fromText $ "reduce_sim_" <> toText a <> ".v") synth
where
synth src = liftSh . runInTmp $ do
diff --git a/src/Verismith/Tool/Identity.hs b/src/Verismith/Tool/Identity.hs
index 9e436f3..8f6901f 100644
--- a/src/Verismith/Tool/Identity.hs
+++ b/src/Verismith/Tool/Identity.hs
@@ -25,8 +25,8 @@ import Verismith.Tool.Internal
import Verismith.Verilog.AST
import Verismith.Verilog.CodeGen
-data Identity = Identity { identityDesc :: {-# UNPACK #-} !Text
- , identityOutput :: {-# UNPACK #-} !FilePath
+data Identity = Identity { identityDesc :: !Text
+ , identityOutput :: !FilePath
}
deriving (Eq)
diff --git a/src/Verismith/Tool/Quartus.hs b/src/Verismith/Tool/Quartus.hs
index fd999ee..e6624eb 100644
--- a/src/Verismith/Tool/Quartus.hs
+++ b/src/Verismith/Tool/Quartus.hs
@@ -27,8 +27,8 @@ import Verismith.Verilog.AST
import Verismith.Verilog.CodeGen
data Quartus = Quartus { quartusBin :: !(Maybe FilePath)
- , quartusDesc :: {-# UNPACK #-} !Text
- , quartusOutput :: {-# UNPACK #-} !FilePath
+ , quartusDesc :: !Text
+ , quartusOutput :: !FilePath
}
deriving (Eq)
diff --git a/src/Verismith/Tool/QuartusLight.hs b/src/Verismith/Tool/QuartusLight.hs
index 881ef8e..f703da0 100644
--- a/src/Verismith/Tool/QuartusLight.hs
+++ b/src/Verismith/Tool/QuartusLight.hs
@@ -27,8 +27,8 @@ import Verismith.Verilog.AST
import Verismith.Verilog.CodeGen
data QuartusLight = QuartusLight { quartusLightBin :: !(Maybe FilePath)
- , quartusLightDesc :: {-# UNPACK #-} !Text
- , quartusLightOutput :: {-# UNPACK #-} !FilePath
+ , quartusLightDesc :: !Text
+ , quartusLightOutput :: !FilePath
}
deriving (Eq)
diff --git a/src/Verismith/Tool/Vivado.hs b/src/Verismith/Tool/Vivado.hs
index e3d2538..35cda2e 100644
--- a/src/Verismith/Tool/Vivado.hs
+++ b/src/Verismith/Tool/Vivado.hs
@@ -27,8 +27,8 @@ import Verismith.Verilog.AST
import Verismith.Verilog.CodeGen
data Vivado = Vivado { vivadoBin :: !(Maybe FilePath)
- , vivadoDesc :: {-# UNPACK #-} !Text
- , vivadoOutput :: {-# UNPACK #-} !FilePath
+ , vivadoDesc :: !Text
+ , vivadoOutput :: !FilePath
}
deriving (Eq)
diff --git a/src/Verismith/Tool/XST.hs b/src/Verismith/Tool/XST.hs
index 4a4921c..2bec7d9 100644
--- a/src/Verismith/Tool/XST.hs
+++ b/src/Verismith/Tool/XST.hs
@@ -30,8 +30,8 @@ import Verismith.Verilog.AST
import Verismith.Verilog.CodeGen
data XST = XST { xstBin :: !(Maybe FilePath)
- , xstDesc :: {-# UNPACK #-} !Text
- , xstOutput :: {-# UNPACK #-} !FilePath
+ , xstDesc :: !Text
+ , xstOutput :: !FilePath
}
deriving (Eq)
diff --git a/src/Verismith/Tool/Yosys.hs b/src/Verismith/Tool/Yosys.hs
index 3632f37..9f536b7 100644
--- a/src/Verismith/Tool/Yosys.hs
+++ b/src/Verismith/Tool/Yosys.hs
@@ -39,8 +39,8 @@ import Verismith.Verilog.CodeGen
import Verismith.Verilog.Mutate
data Yosys = Yosys { yosysBin :: !(Maybe FilePath)
- , yosysDesc :: {-# UNPACK #-} !Text
- , yosysOutput :: {-# UNPACK #-} !FilePath
+ , yosysDesc :: !Text
+ , yosysOutput :: !FilePath
}
deriving (Eq)
diff --git a/src/Verismith/Verilog/AST.hs b/src/Verismith/Verilog/AST.hs
index 74c3cfb..3d7c96e 100644
--- a/src/Verismith/Verilog/AST.hs
+++ b/src/Verismith/Verilog/AST.hs
@@ -618,9 +618,11 @@ aModule t = lens get_ set_
SourceInfo top (main & getModule %~ update (getIdentifier t) v)
update top v m@(ModDecl (Identifier i) _ _ _ _) | i == top = v
| otherwise = m
+ update top v (ModDeclAnn _ m) = update top v m
get_ (SourceInfo _ main) =
head . filter (f $ getIdentifier t) $ main ^.. getModule
f top (ModDecl (Identifier i) _ _ _ _) = i == top
+ f top (ModDeclAnn _ m) = f top m
-- | May need to change this to Traversal to be safe. For now it will fail when
@@ -632,5 +634,7 @@ mainModule = lens get_ set_
SourceInfo top (main & getModule %~ update top v)
update top v m@(ModDecl (Identifier i) _ _ _ _) | i == top = v
| otherwise = m
+ update top v (ModDeclAnn _ m) = update top v m
get_ (SourceInfo top main) = head . filter (f top) $ main ^.. getModule
f top (ModDecl (Identifier i) _ _ _ _) = i == top
+ f top (ModDeclAnn _ m) = f top m