Skip to content

Commit

Permalink
Merge pull request #2007 from clash-lang/fix2001
Browse files Browse the repository at this point in the history
First active edge at least one clock period from start
  • Loading branch information
martijnbastiaan authored Feb 2, 2022
2 parents f68df2f + a5c1ea5 commit a6e5122
Show file tree
Hide file tree
Showing 18 changed files with 73 additions and 37 deletions.
2 changes: 1 addition & 1 deletion .ci/gitlab/common.yml
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
timeout: 2 hours
stage: build
variables:
CACHE_FALLBACK_KEY: $CI_JOB_NAME-master-$GHC_VERSION
CACHE_FALLBACK_KEY: $CI_JOB_NAME-master-$GHC_VERSION-3
GIT_SUBMODULE_STRATEGY: recursive
TERM: xterm-color
retry:
Expand Down
1 change: 1 addition & 0 deletions changelog/2021-11-19T17_41_41+01_00_fix2001
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
FIXED: Clash now generates clock generators that ensure that the amount of time between simulation start and the first active edge of the clock is equal to (/or longer than/) the period of the clock. The first active edges of the clocks do still occur simultaneously. [#2001](https://github.com/clash-lang/clash-compiler/issues/2001)
Original file line number Diff line number Diff line change
Expand Up @@ -75,7 +75,7 @@ localparam ~GENSYM[half_period][0] = (~PERIOD[0]0 / 2);
always begin
~RESULT = ~IF~ACTIVEEDGE[Rising][0]~THEN 0 ~ELSE 1 ~FI;
`ifndef VERILATOR
#30000 forever begin
#~LONGESTPERIOD0 forever begin
if (~ ~ARG[1]) begin
$finish;
end
Expand All @@ -92,7 +92,7 @@ end
`ifdef VERILATOR
`systemc_interface
CData ~SYM[1](vluint32_t half_period, bool active_rising, bool result_rec) {
static vluint32_t init_wait = 30000;
static vluint32_t init_wait = ~LONGESTPERIOD0;
static vluint32_t to_wait = 0;
static CData clock = active_rising ? 0 : 1;

Expand Down
10 changes: 3 additions & 7 deletions clash-lib/prims/systemverilog/Clash_Signal_Internal.primitives
Original file line number Diff line number Diff line change
Expand Up @@ -98,7 +98,7 @@ localparam ~GENSYM[half_period][0] = (~PERIOD[0]0 / 2);
always begin
~RESULT = ~IF~ACTIVEEDGE[Rising][0]~THEN 0 ~ELSE 1 ~FI;
`ifndef VERILATOR
#30000 forever begin
#~LONGESTPERIOD0 forever begin
~RESULT = ~ ~RESULT;
#~SYM[0];
~RESULT = ~ ~RESULT;
Expand All @@ -112,7 +112,7 @@ end
`ifdef VERILATOR
`systemc_interface
CData ~SYM[1](vluint32_t half_period, bool active_rising) {
static vluint32_t init_wait = 30000;
static vluint32_t init_wait = ~LONGESTPERIOD0;
static vluint32_t to_wait = 0;
static CData clock = active_rising ? 0 : 1;

Expand Down Expand Up @@ -146,11 +146,7 @@ end
, "template" :
"// resetGen begin
// pragma translate_off
~IF~ISSYNC[0]~THEN
localparam ~GENSYM[reset_period][0] = 29998 + (~LIT[2] * ~PERIOD[0]0);
~ELSE
localparam ~SYM[0] = 30001 + ((~LIT[2] - 1) * ~PERIOD[0]0);
~FI
localparam ~GENSYM[reset_period][0] = ~LONGESTPERIOD0 - 10 + (~LIT[2] * ~PERIOD[0]0);
`ifndef VERILATOR
initial begin
#1 ~RESULT = ~IF ~ISACTIVEHIGH[0] ~THEN 1 ~ELSE 0 ~FI;
Expand Down
4 changes: 2 additions & 2 deletions clash-lib/prims/verilog/Clash_Explicit_Testbench.primitives
Original file line number Diff line number Diff line change
Expand Up @@ -77,7 +77,7 @@ always begin
// Delay of 1 mitigates race conditions (https://github.com/steveicarus/iverilog/issues/160)
#1 ~SYM[0] = ~IF~ACTIVEEDGE[Rising][0]~THEN 0 ~ELSE 1 ~FI;
`ifndef VERILATOR
#30000 forever begin
#~LONGESTPERIOD0 forever begin
if (~ ~ARG[1]) begin
$finish;
end
Expand All @@ -94,7 +94,7 @@ end
`ifdef VERILATOR
`systemc_interface
CData ~SYM[2](vluint32_t half_period, bool active_rising, bool result_rec) {
static vluint32_t init_wait = 30000;
static vluint32_t init_wait = ~LONGESTPERIOD0;
static vluint32_t to_wait = 0;
static CData clock = active_rising ? 0 : 1;

Expand Down
10 changes: 3 additions & 7 deletions clash-lib/prims/verilog/Clash_Signal_Internal.primitives
Original file line number Diff line number Diff line change
Expand Up @@ -103,7 +103,7 @@ always begin
// Delay of 1 mitigates race conditions (https://github.com/steveicarus/iverilog/issues/160)
#1 ~SYM[0] = ~IF~ACTIVEEDGE[Rising][0]~THEN 0 ~ELSE 1 ~FI;
`ifndef VERILATOR
#30000 forever begin
#~LONGESTPERIOD0 forever begin
~SYM[0] = ~ ~SYM[0];
#~SYM[1];
~SYM[0] = ~ ~SYM[0];
Expand All @@ -117,7 +117,7 @@ end
`ifdef VERILATOR
`systemc_interface
CData ~SYM[2](vluint32_t half_period, bool active_rising) {
static vluint32_t init_wait = 30000;
static vluint32_t init_wait = ~LONGESTPERIOD0;
static vluint32_t to_wait = 0;
static CData clock = active_rising ? 0 : 1;

Expand Down Expand Up @@ -153,11 +153,7 @@ assign ~RESULT = ~SYM[0];
"// resetGen begin
// pragma translate_off
reg ~TYPO ~GENSYM[rst][0];
~IF~ISSYNC[0]~THEN
localparam ~GENSYM[reset_period][1] = 29998 + (~LIT[2] * ~PERIOD[0]0);
~ELSE
localparam ~SYM[1] = 30001 + ((~LIT[2] - 1) * ~PERIOD[0]0);
~FI
localparam ~GENSYM[reset_period][1] = ~LONGESTPERIOD0 - 10 + (~LIT[2] * ~PERIOD[0]0);
`ifndef VERILATOR
initial begin
#1 ~SYM[0] = ~IF ~ISACTIVEHIGH[0] ~THEN 1 ~ELSE 0 ~FI;
Expand Down
2 changes: 1 addition & 1 deletion clash-lib/prims/vhdl/Clash_Explicit_Testbench.primitives
Original file line number Diff line number Diff line change
Expand Up @@ -175,7 +175,7 @@ end block;
constant ~GENSYM[half_periodL][2] : time := ~PERIOD[0]000 fs - ~SYM[1];
begin
~RESULT <= ~IF~ACTIVEEDGE[Rising][0]~THEN'0'~ELSE'1'~FI;
wait for 3000 ps;
wait for ~LONGESTPERIOD ps;
while ~ARG[1] loop
~RESULT <= not ~RESULT;
wait for ~SYM[1];
Expand Down
11 changes: 8 additions & 3 deletions clash-lib/prims/vhdl/Clash_Signal_Internal.primitives
Original file line number Diff line number Diff line change
Expand Up @@ -145,7 +145,7 @@ end process;~FI~FI
constant ~GENSYM[half_periodL][2] : time := ~PERIOD[0]000 fs - ~SYM[1];
begin
~RESULT <= ~IF~ACTIVEEDGE[Rising][0]~THEN'0'~ELSE'1'~FI;
wait for 3000 ps;
wait for ~LONGESTPERIOD ps;
loop
~RESULT <= not ~RESULT;
wait for ~SYM[1];
Expand All @@ -165,10 +165,15 @@ end process;
, "type" : "resetGenN :: (KnownDomain dom, 1 <= n) => SNat n -> Reset dom"
, "template" :
"-- resetGen begin
~GENSYM[resetGen][0] : block
constant ~GENSYM[reset_delay][1] : time := ~LONGESTPERIOD ps - 1 ps + (integer'(~LIT[2]) * ~PERIOD[0] ps);
begin
-- pragma translate_off
~RESULT <= ~IF ~ISACTIVEHIGH[0] ~THEN '1' ~ELSE '0' ~FI,
~IF ~ISACTIVEHIGH[0] ~THEN '0' ~ELSE '1' ~FI after ~IF~ISSYNC[0]~THEN(2999 ps + (integer'(~LIT[2]) * ~PERIOD[0] ps))~ELSE(3001 ps + integer'(~LIT[2] - 1) * ~PERIOD[0] ps)~FI;
~RESULT
<= ~IF ~ISACTIVEHIGH[0] ~THEN'1'~ELSE'0'~FI,
~IF ~ISACTIVEHIGH[0] ~THEN'0'~ELSE'1'~FI after ~SYM[1];
-- pragma translate_on
end block;
-- resetGen end"
}
}
Expand Down
11 changes: 11 additions & 0 deletions clash-lib/src/Clash/Backend.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@

module Clash.Backend where

import Data.HashMap.Strict (HashMap, empty)
import Data.HashSet (HashSet)
import Data.Monoid (Ap)
import Data.Text (Text)
Expand All @@ -28,6 +29,7 @@ import Clash.Driver.Types (ClashOpts)
import {-# SOURCE #-} Clash.Netlist.Types
import Clash.Netlist.BlackBox.Types

import Clash.Signal.Internal (VDomainConfiguration)
import Clash.Annotations.Primitive (HDL)

#ifdef CABAL
Expand Down Expand Up @@ -79,6 +81,11 @@ data HWKind
-- ^ User defined type that's not interchangeable with any others, even if
-- the underlying structures are the same. Similar to an ADT in Haskell.

type DomainMap = HashMap Text VDomainConfiguration

emptyDomainMap :: DomainMap
emptyDomainMap = empty

class HasIdentifierSet state => Backend state where
-- | Initial state for state monad
initBackend :: ClashOpts -> state
Expand Down Expand Up @@ -151,3 +158,7 @@ class HasIdentifierSet state => Backend state where
aggressiveXOptBB :: State state AggressiveXOptBB
-- | Whether -fclash-no-render-enums was set
renderEnums :: State state RenderEnums
-- | All the domain configurations of design
domainConfigurations :: State state DomainMap
-- | Set the domain configurations
setDomainConfigurations :: DomainMap -> state -> state
4 changes: 4 additions & 0 deletions clash-lib/src/Clash/Backend/SystemVerilog.hs
Original file line number Diff line number Diff line change
Expand Up @@ -91,6 +91,7 @@ data SystemVerilogState =
, _undefValue :: Maybe (Maybe Int)
, _aggressiveXOptBB_ :: AggressiveXOptBB
, _renderEnums_ :: RenderEnums
, _domainConfigurations_ :: DomainMap
}

makeLenses ''SystemVerilogState
Expand Down Expand Up @@ -118,6 +119,7 @@ instance Backend SystemVerilogState where
, _undefValue=opt_forceUndefined opts
, _aggressiveXOptBB_=coerce (opt_aggressiveXOptBB opts)
, _renderEnums_=coerce (opt_renderEnums opts)
, _domainConfigurations_=emptyDomainMap
}
hdlKind = const SystemVerilog
primDirs = const $ do root <- primsRoot
Expand Down Expand Up @@ -184,6 +186,8 @@ instance Backend SystemVerilogState where
ifThenElseExpr _ = True
aggressiveXOptBB = use aggressiveXOptBB_
renderEnums = use renderEnums_
domainConfigurations = use domainConfigurations_
setDomainConfigurations confs s = s {_domainConfigurations_ = confs}

type SystemVerilogM a = Ap (State SystemVerilogState) a

Expand Down
4 changes: 4 additions & 0 deletions clash-lib/src/Clash/Backend/VHDL.hs
Original file line number Diff line number Diff line change
Expand Up @@ -113,6 +113,7 @@ data VHDLState =
-- ^ Cache for enum variant names.
, _aggressiveXOptBB_ :: AggressiveXOptBB
, _renderEnums_ :: RenderEnums
, _domainConfigurations_ :: DomainMap
}

makeLenses ''VHDLState
Expand Down Expand Up @@ -140,6 +141,7 @@ instance Backend VHDLState where
, _enumNameCache=mempty
, _aggressiveXOptBB_=coerce (opt_aggressiveXOptBB opts)
, _renderEnums_=coerce (opt_renderEnums opts)
, _domainConfigurations_=emptyDomainMap
}
hdlKind = const VHDL
primDirs = const $ do root <- primsRoot
Expand Down Expand Up @@ -264,6 +266,8 @@ instance Backend VHDLState where
ifThenElseExpr _ = False
aggressiveXOptBB = use aggressiveXOptBB_
renderEnums = use renderEnums_
domainConfigurations = use domainConfigurations_
setDomainConfigurations confs s = s {_domainConfigurations_ = confs}

type VHDLM a = Ap (State VHDLState) a

Expand Down
4 changes: 4 additions & 0 deletions clash-lib/src/Clash/Backend/Verilog.hs
Original file line number Diff line number Diff line change
Expand Up @@ -99,6 +99,7 @@ data VerilogState =
, _hdlsyn :: HdlSyn
, _undefValue :: Maybe (Maybe Int)
, _aggressiveXOptBB_ :: AggressiveXOptBB
, _domainConfigurations_ :: DomainMap
}

makeLenses ''VerilogState
Expand All @@ -121,6 +122,7 @@ instance Backend VerilogState where
, _hdlsyn=opt_hdlSyn opts
, _undefValue=opt_forceUndefined opts
, _aggressiveXOptBB_=coerce (opt_aggressiveXOptBB opts)
, _domainConfigurations_=emptyDomainMap
}
hdlKind = const Verilog
primDirs = const $ do root <- primsRoot
Expand Down Expand Up @@ -184,6 +186,8 @@ instance Backend VerilogState where
ifThenElseExpr _ = True
aggressiveXOptBB = use aggressiveXOptBB_
renderEnums = pure (RenderEnums False)
domainConfigurations = use domainConfigurations_
setDomainConfigurations confs s = s {_domainConfigurations_ = confs}

type VerilogM a = Ap (State VerilogState) a

Expand Down
3 changes: 2 additions & 1 deletion clash-lib/src/Clash/Driver.hs
Original file line number Diff line number Diff line change
Expand Up @@ -381,7 +381,8 @@ generateHDL env design hdlState typeTrans peEval eval mainTopEntity startTime =
let topNm = lookupVarEnv' compNames topEntity
(modNameS, fmap Data.Text.pack -> prefixM) = prefixModuleName (hdlKind (undefined :: backend)) (opt_componentPrefix opts) annM modName1
modNameT = Data.Text.pack modNameS
hdlState' = setModName modNameT
hdlState' = setDomainConfigurations domainConfs
$ setModName modNameT
$ fromMaybe (initBackend @backend opts) hdlState
hdlDir = fromMaybe (Clash.Backend.name hdlState') (opt_hdlDir opts) </> topEntityS
manPath = hdlDir </> manifestFilename
Expand Down
6 changes: 4 additions & 2 deletions clash-lib/src/Clash/Netlist/BlackBox/Parser.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,9 @@
{-|
Copyright : (C) 2012-2016, University of Twente,
2017 , Myrtle Software Ltd
2017 , Myrtle Software Ltd,
2021 , QBayLogic B.V.
License : BSD2 (see the file LICENSE)
Maintainer : Christiaan Baaij <christiaan.baaij@gmail.com>
Maintainer : QBayLogic B.V. <devops@qbaylogic.com>
Parser definitions for BlackBox templates
-}
Expand Down Expand Up @@ -128,6 +129,7 @@ pTagE = Result <$ string "~RESULT"
<|> IsSync <$> (string "~ISSYNC" *> brackets' natural')
<|> IsInitDefined <$> (string "~ISINITDEFINED" *> brackets' natural')
<|> CtxName <$ string "~CTXNAME"
<|> LongestPeriod <$ string "~LONGESTPERIOD"

natural' :: TokenParsing m => m Int
natural' = fmap fromInteger natural
Expand Down
4 changes: 3 additions & 1 deletion clash-lib/src/Clash/Netlist/BlackBox/Types.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-|
Copyright : (C) 2012-2016, University of Twente,
2017 , Myrtle Software Ltd,
2022 , QBayLogic B.V.
2021-2022, QBayLogic B.V.
License : BSD2 (see the file LICENSE)
Maintainer : QBayLogic B.V. <devops@qbaylogic.com>
Expand Down Expand Up @@ -171,6 +171,8 @@ data Element
-- ^ Tag of a domain.
| Period !Int
-- ^ Period of a domain.
| LongestPeriod
-- ^ Longest period of all known domains
| ActiveEdge !Signal.ActiveEdge !Int
-- ^ Test active edge of memory elements in a certain domain
| IsSync !Int
Expand Down
11 changes: 10 additions & 1 deletion clash-lib/src/Clash/Netlist/BlackBox/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,7 @@ import Data.Bool (bool)
import Data.Coerce (coerce)
import Data.Foldable (foldrM)
import Data.Hashable (Hashable (..))
import qualified Data.HashMap.Strict as HashMap
import qualified Data.IntMap as IntMap
import Data.List (nub)
import Data.List.Extra (indexMaybe)
Expand Down Expand Up @@ -63,7 +64,7 @@ import qualified Clash.Netlist.Id as Id
import qualified Clash.Netlist.Types as N
import Clash.Netlist.Util (typeSize, isVoid, stripVoid)
import Clash.Signal.Internal
(ResetKind(..), ResetPolarity(..), InitBehavior(..))
(ResetKind(..), ResetPolarity(..), InitBehavior(..), VDomainConfiguration (..))
import Clash.Util
import qualified Clash.Util.Interpolate as I

Expand Down Expand Up @@ -403,6 +404,11 @@ renderElem b (Period n) = do
_ ->
error $ $(curLoc) ++ "Period: Expected `KnownDomain` or `KnownConfiguration`, not: " ++ show ty

renderElem _ LongestPeriod = do
doms <- domainConfigurations
let longestPeriod = maximum [vPeriod v | v <- HashMap.elems doms]
return (const (Text.pack (show longestPeriod)))

renderElem b (Tag n) = do
let (_, ty, _) = bbInputs b !! n
case stripVoid ty of
Expand Down Expand Up @@ -932,6 +938,7 @@ prettyElem (IsUndefined i) = renderOneLine <$> (string "~ISUNDEFINED" <> bracket
-- Domain attributes:
prettyElem (Tag i) = renderOneLine <$> (string "~TAG" <> brackets (int i))
prettyElem (Period i) = renderOneLine <$> (string "~PERIOD" <> brackets (int i))
prettyElem LongestPeriod = return "~LONGESTPERIOD"
prettyElem (ActiveEdge e i) = renderOneLine <$> (string "~ACTIVEEDGE" <> brackets (string (Text.pack (show e))) <> brackets (int i))
prettyElem (IsSync i) = renderOneLine <$> (string "~ISSYNC" <> brackets (int i))
prettyElem (IsInitDefined i) = renderOneLine <$> (string "~ISINITDEFINED" <> brackets (int i))
Expand Down Expand Up @@ -1032,6 +1039,7 @@ walkElement f el = maybeToList (f el) ++ walked
IsVar _ -> []
Tag _ -> []
Period _ -> []
LongestPeriod -> []
ActiveEdge _ _ -> []
IsSync _ -> []
IsInitDefined _ -> []
Expand Down Expand Up @@ -1091,6 +1099,7 @@ getUsedArguments (N.BBTemplate t) = nub (concatMap (walkElement matchArg) t)
ActiveEdge _ _ -> Nothing
IsSync _ -> Nothing
Period _ -> Nothing
LongestPeriod -> Nothing
Tag _ -> Nothing

-- Others. Template tags only using types of arguments can be considered
Expand Down
Loading

0 comments on commit a6e5122

Please sign in to comment.