aboutsummaryrefslogtreecommitdiffstats
path: root/src
diff options
context:
space:
mode:
authorYann Herklotz <git@yannherklotz.com>2019-07-20 19:38:01 +0100
committerYann Herklotz <git@yannherklotz.com>2019-07-20 19:38:01 +0100
commit7d69341adfef072e46098a5b377a22ab4ce610dd (patch)
treef2af69a57cca91dc754395b88b7bd09ab42b0c7a /src
parent562f0da77e0464bfc21e8753070aec1cf9e60cf2 (diff)
downloadverismith-7d69341adfef072e46098a5b377a22ab4ce610dd.tar.gz
verismith-7d69341adfef072e46098a5b377a22ab4ce610dd.zip
Multiple initialisations now appearing
Diffstat (limited to 'src')
-rw-r--r--src/VeriFuzz/Fuzz.hs4
-rw-r--r--src/VeriFuzz/Verilog/Gen.hs26
2 files changed, 22 insertions, 8 deletions
diff --git a/src/VeriFuzz/Fuzz.hs b/src/VeriFuzz/Fuzz.hs
index 4f5c016..77962b5 100644
--- a/src/VeriFuzz/Fuzz.hs
+++ b/src/VeriFuzz/Fuzz.hs
@@ -91,8 +91,8 @@ synthesisers = lift $ asks getSynthesisers
--simulators :: (Monad m) => Fuzz () m [SimTool]
--simulators = lift $ asks getSimulators
-combinations :: [a] -> [b] -> [(a, b)]
-combinations l1 l2 = [ (x, y) | x <- l1, y <- l2 ]
+--combinations :: [a] -> [b] -> [(a, b)]
+--combinations l1 l2 = [ (x, y) | x <- l1, y <- l2 ]
logT :: MonadSh m => Text -> m ()
logT = liftSh . logger
diff --git a/src/VeriFuzz/Verilog/Gen.hs b/src/VeriFuzz/Verilog/Gen.hs
index 2331068..f2d2b0a 100644
--- a/src/VeriFuzz/Verilog/Gen.hs
+++ b/src/VeriFuzz/Verilog/Gen.hs
@@ -11,6 +11,7 @@ Various useful generators.
-}
{-# LANGUAGE TemplateHaskell #-}
+{-# OPTIONS_GHC -Wno-unused-imports #-}
module VeriFuzz.Verilog.Gen
( -- * Generation methods
@@ -42,6 +43,10 @@ import VeriFuzz.Verilog.Eval
import VeriFuzz.Verilog.Internal
import VeriFuzz.Verilog.Mutate
+-- Temporary imports
+import Debug.Trace
+import VeriFuzz.Verilog.CodeGen
+
data Context = Context { _variables :: [Port]
, _parameters :: [Parameter]
, _modules :: [ModDecl]
@@ -350,21 +355,27 @@ statement = do
alwaysSeq :: StateGen ModItem
alwaysSeq = Always . EventCtrl (EPosEdge "clk") . Just <$> seqBlock
-resizePort :: Port -> Port -> StateGen ()
-resizePort (Port _ _ _ i) (Port _ _ ra _) = variables %= repl
+-- | Should resize a port that connects to a module port if the latter is
+-- larger. This should not cause any problems if the same net is used as input
+-- multiple times, and is resized multiple times, as it should only get larger.
+resizePort :: [Parameter] -> Identifier -> Range -> [Port] -> [Port]
+resizePort ps i ra = foldl' func []
where
- repl = foldl' func []
- func l p@(Port a b _ i')
- | i' == i = Port a b ra i : l
+ func l p@(Port _ _ ri i')
+ | i' == i && calc ri < calc ra = (p & portSize .~ ra) : l
| otherwise = p : l
+ calc = calcRange ps $ Just 64
+-- | Instantiate a module, where the outputs are new nets that are created, and
+-- the inputs are taken from existing ports in the context.
instantiate :: ModDecl -> StateGen ModItem
instantiate (ModDecl i outP inP _ _) = do
context <- get
outs <- replicateM (length outP) (nextPort Wire)
ins <- take (length inP) <$> Hog.shuffle (context ^. variables)
- sequence_ $ uncurry resizePort <$> zip (outs <> ins) (outP <> inP)
+ mapM_ (uncurry process) . zip (ins ^.. traverse . portName) $ inP ^.. traverse . portSize
ident <- makeIdentifier "modinst"
+ vs <- view variables <$> get
Hog.choice
[ return . ModInst i ident $ ModConn <$> outE outs <> insE ins
, ModInst i ident <$> Hog.shuffle
@@ -373,6 +384,9 @@ instantiate (ModDecl i outP inP _ _) = do
where
insE ins = Id "clk" : (Id . view portName <$> ins)
outE out = Id . view portName <$> out
+ process p r = do
+ params <- view parameters <$> get
+ variables %= resizePort params p r
-- | Generates a module instance by also generating a new module if there are
-- not enough modules currently in the context. It keeps generating new modules