Skip to content

Commit

Permalink
Properly recognize workfree enable signals (#1936)
Browse files Browse the repository at this point in the history
isWorkFreeClockOrResetOrEnable tried to detect constant enable signals,
but we forgot to update this when we changed the representation
of Enable in #1368.

This fixes the register duplication issue seen in #1935
  • Loading branch information
leonschoorl authored Sep 29, 2021
1 parent b4ddd62 commit 0415bcf
Show file tree
Hide file tree
Showing 4 changed files with 53 additions and 1 deletion.
1 change: 1 addition & 0 deletions changelog/2021-09-28T18_46_48+02_00_fix_1935
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
FIXED: Recognize enableGen as workfree and don't duplicate registers [#1935](https://github.com/clash-lang/clash-compiler/issues/1935)
2 changes: 1 addition & 1 deletion clash-lib/src/Clash/Rewrite/WorkFree.hs
Original file line number Diff line number Diff line change
Expand Up @@ -155,7 +155,7 @@ isWorkFreeClockOrResetOrEnable tcm e =
case collectArgs e of
(Prim p,_) -> Just (primName p == Text.showt 'removedArg)
(Var _, []) -> Just True
(Data _, []) -> Just True -- For Enable True/False
(Data _, [_dom, Left (stripTicks -> Data _)]) -> Just True -- For Enable True/False
(Literal _,_) -> Just True
_ -> Just False
else
Expand Down
1 change: 1 addition & 0 deletions tests/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -562,6 +562,7 @@ runClashTest = defaultMain $ clashTestRoot
[ clashLibTest "Identity" def
, clashLibTest "NoDeDup" def{hdlTargets=[VHDL]}
, clashLibTest "T1766" def
, clashLibTest "T1935" def
]
, clashTestGroup "Numbers"
[ runTest "BitInteger" def
Expand Down
50 changes: 50 additions & 0 deletions tests/shouldwork/Netlist/T1935.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,50 @@
{-# LANGUAGE OverloadedStrings #-}
module T1935 where

import qualified Prelude as P

import Clash.Prelude

import Clash.Netlist.Types
import Clash.Backend (Backend)

import Test.Tasty.Clash
import Test.Tasty.Clash.NetlistTest

import Control.Monad (when)

topEntity
:: Clock System
-> Reset System
-> Signal System (Unsigned 8)
topEntity clk rst = withClockResetEnable clk rst enableGen x
where
x :: SystemClockResetEnable => Signal System (Unsigned 8)
x = register 4 (x+1)

testPath :: FilePath
testPath = "tests/shouldwork/Netlist/T1935.hs"

countRegisters :: Component -> Int
countRegisters (Component _nm _inps _outs ds) =
let regs = filter isRegister ds
in P.length regs
where
isRegister (BlackBoxD nm _ _ _ _ _)
| nm == "Clash.Signal.Internal.register#" = True
isRegister _ = False

mainGeneric :: Backend (TargetToState target) => SBuildTarget target -> IO ()
mainGeneric hdl = do
netlist <- runToNetlistStage hdl id testPath
let regs = sum $ fmap (countRegisters . snd) netlist
when (regs /= 1) $ error ("Expected 1 register, but found: " <> show regs)

mainVHDL :: IO ()
mainVHDL = mainGeneric SVHDL

mainVerilog :: IO ()
mainVerilog = mainGeneric SVerilog

mainSystemVerilog :: IO ()
mainSystemVerilog = mainGeneric SSystemVerilog

0 comments on commit 0415bcf

Please sign in to comment.