Skip to content

Commit

Permalink
allow usage declarations (for unique names)
Browse files Browse the repository at this point in the history
All CondAssign should be reg etc.
  • Loading branch information
vmchale committed Jun 27, 2022
1 parent 619cb8b commit 1c8d33c
Show file tree
Hide file tree
Showing 5 changed files with 15 additions and 3 deletions.
2 changes: 2 additions & 0 deletions clash-lib/src/Clash/Backend.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@ module Clash.Backend where

import Data.HashMap.Strict (HashMap, empty)
import Data.HashSet (HashSet)
import Control.Lens (Lens')
import Data.Monoid (Ap)
import Data.Text (Text)
import qualified Data.Text.Lazy as LT
Expand Down Expand Up @@ -167,3 +168,4 @@ class HasIdentifierSet state => Backend state where
domainConfigurations :: State state DomainMap
-- | Set the domain configurations
setDomainConfigurations :: DomainMap -> state -> state
usageMap :: Lens' state UsageMap
1 change: 1 addition & 0 deletions clash-lib/src/Clash/Backend/SystemVerilog.hs
Original file line number Diff line number Diff line change
Expand Up @@ -195,6 +195,7 @@ instance Backend SystemVerilogState where
renderEnums = use renderEnums_
domainConfigurations = use domainConfigurations_
setDomainConfigurations confs s = s {_domainConfigurations_ = confs}
usageMap = usages

type SystemVerilogM a = Ap (State SystemVerilogState) a

Expand Down
1 change: 1 addition & 0 deletions clash-lib/src/Clash/Backend/VHDL.hs
Original file line number Diff line number Diff line change
Expand Up @@ -284,6 +284,7 @@ instance Backend VHDLState where
renderEnums = use renderEnums_
domainConfigurations = use domainConfigurations_
setDomainConfigurations confs s = s {_domainConfigurations_ = confs}
usageMap = usages

type VHDLM a = Ap (State VHDLState) a

Expand Down
1 change: 1 addition & 0 deletions clash-lib/src/Clash/Backend/Verilog.hs
Original file line number Diff line number Diff line change
Expand Up @@ -195,6 +195,7 @@ instance Backend VerilogState where
renderEnums = pure (RenderEnums False)
domainConfigurations = use domainConfigurations_
setDomainConfigurations confs s = s {_domainConfigurations_ = confs}
usageMap = usages

type VerilogM a = Ap (State VerilogState) a

Expand Down
13 changes: 10 additions & 3 deletions clash-lib/src/Clash/Primitives/DSL.hs
Original file line number Diff line number Diff line change
Expand Up @@ -91,6 +91,7 @@ import Data.IntMap (IntMap)
import qualified Data.IntMap as IntMap
import Data.List (intersperse)
import Data.List.Extra (zipEqual)
import qualified Data.Map as Map
import Data.Maybe (fromMaybe)
import Data.Monoid (Ap(getAp))
import Data.Semigroup hiding (Product)
Expand All @@ -102,15 +103,15 @@ import Data.Text.Prettyprint.Doc.Extra
import GHC.Stack (HasCallStack)

import Clash.Annotations.Primitive (HDL (..), Primitive (..))
import Clash.Backend hiding (fromBV, toBV)
import Clash.Backend hiding (Usage, fromBV, toBV)
import Clash.Backend.VHDL (VHDLState)
import Clash.Core.Var (Attr')
import Clash.Netlist.BlackBox.Util (exprToString, renderElem)
import Clash.Netlist.BlackBox.Types
(BlackBoxTemplate, Element(Component, Text), Decl(..))
import qualified Clash.Netlist.Id as Id
import Clash.Netlist.Types hiding (Component, toBit)
import Clash.Netlist.Util
import Clash.Netlist.Types hiding (Component, toBit, usageMap)
import Clash.Netlist.Util hiding (declareUse)
import Clash.Util (clogBase)
import qualified Data.String.Interpolate as I
import Data.String.Interpolate.Util (unindent)
Expand Down Expand Up @@ -415,6 +416,7 @@ boolToBit bitName = \case
[ (Just (BoolLit True), Literal Nothing (BitLit H))
, (Nothing , Literal Nothing (BitLit L))
]
declareUse (Proc Blocking) uniqueBitName
pure texp
tExpr -> error $ "boolToBit: Got \"" <> show tExpr <> "\" expected Bool"

Expand All @@ -434,9 +436,13 @@ enableToBit bitName = \case
[ (Just (BoolLit True), Literal Nothing (BitLit H))
, (Nothing , Literal Nothing (BitLit L))
]
declareUse (Proc Blocking) uniqueBitName
pure texp
tExpr -> error $ "enableToBit: Got \"" <> show tExpr <> "\" expected Enable"

declareUse :: Backend backend => Usage -> Identifier -> State (BlockState backend) ()
declareUse u i = bsBackend.usageMap %= Map.insert (Id.toText i) u

-- | Use to create an output `Bool` from a `Bit`. The expression given
-- must be the identifier of the bool you wish to get assigned.
-- Returns a reference to a declared `Bit` that should get assigned
Expand All @@ -457,6 +463,7 @@ boolFromBit boolName = \case
[ (Just (BitLit H), Literal Nothing (BoolLit True))
, (Nothing , Literal Nothing (BoolLit False))
]
declareUse (Proc Blocking) uniqueBoolName
pure texp
tExpr -> error $ "boolFromBit: Got \"" <> show tExpr <> "\" expected Bit"

Expand Down

0 comments on commit 1c8d33c

Please sign in to comment.