File tree 5 files changed +54
-1
lines changed
clash-lib/src/Clash/Rewrite 5 files changed +54
-1
lines changed Original file line number Diff line number Diff line change
1
+ FIXED: Recognize enableGen as workfree and don't duplicate registers [#1935](https://github.com/clash-lang/clash-compiler/issues/1935)
Original file line number Diff line number Diff line change @@ -150,7 +150,7 @@ isWorkFreeClockOrResetOrEnable tcm e =
150
150
case collectArgs e of
151
151
(Prim p,_) -> Just (primName p == " Clash.Transformations.removedArg" )
152
152
(Var _, [] ) -> Just True
153
- (Data _, [] ) -> Just True -- For Enable True/False
153
+ (Data _, [_dom, Left (stripTicks -> Data _) ]) -> Just True -- For Enable True/False
154
154
(Literal _,_) -> Just True
155
155
_ -> Just False
156
156
else
Original file line number Diff line number Diff line change @@ -137,6 +137,7 @@ runClashTest = defaultMain $ clashTestRoot
137
137
[ clashTestGroup " netlist"
138
138
[ clashLibTest (" tests" </> " shouldwork" </> " Netlist" ) allTargets [] " Identity" " main"
139
139
, NEEDS_PRIMS (clashLibTest (" tests" </> " shouldwork" </> " Netlist" ) [VHDL ] [] " NoDeDup" " main" )
140
+ , clashLibTest (" tests" </> " shouldwork" </> " Netlist" ) allTargets [] " T1935" " main"
140
141
]
141
142
, clashTestGroup " examples"
142
143
[ runTest " ALU" def{hdlSim= False }
Original file line number Diff line number Diff line change
1
+ {-# LANGUAGE OverloadedStrings #-}
2
+ module T1935 where
3
+
4
+ import qualified Prelude as P
5
+
6
+ import Clash.Prelude
7
+
8
+ import Clash.Netlist.Types
9
+ import Clash.Backend (Backend )
10
+
11
+ import Test.Tasty.Clash
12
+ import Test.Tasty.Clash.NetlistTest
13
+
14
+ import Control.Monad (when )
15
+
16
+ topEntity
17
+ :: Clock System
18
+ -> Reset System
19
+ -> Signal System (Unsigned 8 )
20
+ topEntity clk rst = withClockResetEnable clk rst enableGen x
21
+ where
22
+ x :: SystemClockResetEnable => Signal System (Unsigned 8 )
23
+ x = register 4 (x+ 1 )
24
+
25
+ testPath :: FilePath
26
+ testPath = " tests/shouldwork/Netlist/T1935.hs"
27
+
28
+ countRegisters :: Component -> Int
29
+ countRegisters (Component _nm _inps _outs ds) =
30
+ let regs = filter isRegister ds
31
+ in P. length regs
32
+ where
33
+ isRegister (BlackBoxD nm _ _ _ _ _)
34
+ | nm == " Clash.Signal.Internal.register#" = True
35
+ isRegister _ = False
36
+
37
+ mainGeneric :: Backend (TargetToState target ) => SBuildTarget target -> IO ()
38
+ mainGeneric hdl = do
39
+ netlist <- runToNetlistStage hdl id testPath
40
+ let regs = sum $ fmap (countRegisters . snd ) netlist
41
+ when (regs /= 1 ) $ error (" Expected 1 register, but found: " <> show regs)
42
+
43
+ mainVHDL :: IO ()
44
+ mainVHDL = mainGeneric SVHDL
45
+
46
+ mainVerilog :: IO ()
47
+ mainVerilog = mainGeneric SVerilog
48
+
49
+ mainSystemVerilog :: IO ()
50
+ mainSystemVerilog = mainGeneric SSystemVerilog
Original file line number Diff line number Diff line change 16
16
--
17
17
module Test.Tasty.Clash.NetlistTest
18
18
( runToNetlistStage
19
+ , TargetToState
19
20
) where
20
21
21
22
import qualified Prelude as P
You can’t perform that action at this time.
0 commit comments