-
Notifications
You must be signed in to change notification settings - Fork 154
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Properly recognize workfree enable signals (#1936)
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
1 parent
b4ddd62
commit 0415bcf
Showing
4 changed files
with
53 additions
and
1 deletion.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 |