Skip to content

Commit 1194408

Browse files
committed
Add annotateReg
a function to add synthesis attributes (e.g. `ASYNC_REG`) to register declarations in the HDL generated by the Clash compiler.
1 parent 5ec337c commit 1194408

File tree

18 files changed

+289
-25
lines changed

18 files changed

+289
-25
lines changed

benchmark/profiling/run/profile-netlist-run.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ import Clash.Netlist
1212
import Clash.Netlist.Types hiding (backend, hdlDir)
1313

1414
import Clash.GHC.NetlistTypes (ghcTypeToHWType)
15+
import Clash.GHC.PartialEval (ghcEvaluator)
1516

1617
import Control.DeepSeq (deepseq)
1718
import Data.Binary (decode)
@@ -62,7 +63,7 @@ benchFile idirs src = do
6263
Clash.Backend.name hdlState' </>
6364
takeWhile (/= '.') topEntityS
6465
(netlist,_,_) <-
65-
genNetlist env False transformedBindings topEntityMap compNames
66+
genNetlist env ghcEvaluator False transformedBindings topEntityMap compNames
6667
(ghcTypeToHWType (opt_intWidth (envOpts env)))
6768
ite (SomeBackend hdlState') seen hdlDir prefixM topEntity
6869
netlist `deepseq` putStrLn ".. done\n"
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
ADDED: `Clash.Annotation.SynthesisAtrributes.annotateReg`, a function to add synthesis attributes (e.g. `ASYNC_REG`) to register declarations in the HDL generated by the Clash compiler.

clash-ghc/src-ghc/Clash/GHC/GHC2Core.hs

Lines changed: 35 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -436,6 +436,9 @@ coreToTerm primMap unlocs = term
436436
-- xToErrorCtx :: forall a. String -> a -> a
437437
| [_ty, _msg, x] <- args
438438
= term x
439+
go "Clash.Annotations.SynthesisAttributes.annotateReg" args
440+
| [ Type nTy, _domTy, _aTy, attrs, x] <- args
441+
= C.Tick <$> (C.Attributes <$> coreToType nTy <*> term attrs) <*> term x
439442
go nm args
440443
| Just n <- parseBundle "bundle" nm
441444
-- length args = domain tyvar + signal arg + number of type vars
@@ -615,6 +618,8 @@ coreToTerm primMap unlocs = term
615618
-> return (nameModTerm C.SetName xType)
616619
| f == "Clash.XException.xToErrorCtx"
617620
-> return (xToErrorCtxTerm xType)
621+
| f == "Clash.Annotations.SynthesisAttributes.annotateReg"
622+
-> return (annotateRegTerm xType)
618623
| x `elem` unlocs
619624
-> return (C.Prim (C.PrimInfo xNameS xType wi C.SingleResult C.NoUnfolding))
620625
| otherwise
@@ -1518,6 +1523,36 @@ xToErrorCtxTerm (C.ForAllTy aTV funTy)
15181523

15191524
xToErrorCtxTerm ty = error $ $(curLoc) ++ show ty
15201525

1526+
-- | Given the type
1527+
--
1528+
-- > forall n dom a . Vec n (Attr String) -> Signal dom a -> Signal dom a
1529+
--
1530+
-- Generate the term:
1531+
--
1532+
-- > /\(n:Nat) (dom:Symbol) (a:Type).\(attrs:Vec n (Attr String)) (x:Signal dom a).<TICK attrs> x
1533+
annotateRegTerm
1534+
:: C.Type
1535+
-> C.Term
1536+
annotateRegTerm (C.ForAllTy nTV (C.ForAllTy domTV (C.ForAllTy aTV funTy)))
1537+
| C.FunTy attrTy rTy <- C.tyView funTy
1538+
, C.FunTy xTy _ <- C.tyView rTy
1539+
= let
1540+
-- Safe to use `mkUnsafeSystemName` here, because we're building the
1541+
-- identity \x.x, so any shadowing of 'x' would be the desired behavior.
1542+
xName = C.mkUnsafeSystemName "x" 0
1543+
xId = C.mkLocalId xTy xName
1544+
attrName = C.mkUnsafeSystemName "attrs" 1
1545+
attrId = C.mkLocalId attrTy attrName
1546+
in
1547+
C.TyLam nTV (
1548+
C.TyLam domTV (
1549+
C.TyLam aTV (
1550+
C.Lam attrId (
1551+
C.Lam xId (
1552+
C.Tick (C.Attributes (C.VarTy nTV) (C.Var attrId)) (C.Var xId))))))
1553+
1554+
annotateRegTerm ty = error ($(curLoc) ++ show ty)
1555+
15211556
isDataConWrapId :: Id -> Bool
15221557
isDataConWrapId v = case idDetails v of
15231558
DataConWrapId {} -> True
Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
- Primitive:
2+
name: Clash.Annotations.SynthesisAttributes.annotateReg
3+
primType: Function

clash-lib/src/Clash/Core/FreeVars.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -281,6 +281,8 @@ termFreeVars' interesting f = go IntSet.empty where
281281

282282
goTick inLocalScope = \case
283283
NameMod m ty -> NameMod m <$> typeFreeVars' interesting inLocalScope f ty
284+
Attributes ty tm -> Attributes <$> typeFreeVars' interesting inLocalScope f ty
285+
<*> go inLocalScope tm
284286
tick -> pure tick
285287

286288
-- | Get the free variables of an expression and count the number of occurrences

clash-lib/src/Clash/Core/Pretty.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -342,6 +342,7 @@ instance PrettyPrec TickInfo where
342342
pprPrec prec (NameMod SetName t) = ("<setName>" <>) <$> pprPrec prec t
343343
pprPrec _ DeDup = pure "<deDup>"
344344
pprPrec _ NoDeDup = pure "<noDeDup>"
345+
pprPrec prec (Attributes _ attrs) = ("<attributes>" <>) <$> pprPrec prec attrs
345346

346347
instance PrettyPrec SrcSpan where
347348
pprPrec _ sp = return ("<src>"<>pretty (GHC.showSDocUnsafe (GHC.ppr sp)))

clash-lib/src/Clash/Core/Subst.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -56,6 +56,7 @@ module Clash.Core.Subst
5656
-- * Alpha equivalence
5757
, aeqType
5858
, aeqTerm
59+
, acmpTerm
5960
-- * Structural equivalence
6061
, eqTerm
6162
, eqType
@@ -584,6 +585,7 @@ substTm doc subst = go where
584585
goTick (NameMod m ty) = NameMod m (substTy subst ty)
585586
goTick t@DeDup = t
586587
goTick t@NoDeDup = t
588+
goTick (Attributes ty tm) = Attributes (substTy subst ty) (go tm)
587589

588590
-- | Substitute within a case-alternative
589591
substAlt

clash-lib/src/Clash/Core/Subst.hs-boot

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
module Clash.Core.Subst where
44

55
import GHC.Stack (HasCallStack)
6+
import {-# SOURCE #-} Clash.Core.Term (Term)
67
import {-# SOURCE #-} Clash.Core.Type (Type)
78
import Clash.Core.Var (TyVar)
89

@@ -20,3 +21,7 @@ aeqType
2021

2122
instance Eq Type
2223
instance Ord Type
24+
25+
aeqTerm :: Term -> Term -> Bool
26+
27+
acmpTerm :: Term -> Term -> Ordering

clash-lib/src/Clash/Core/Term.hs

Lines changed: 18 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -81,7 +81,7 @@ import SrcLoc (SrcSpan, leftmost_smallest)
8181
import Clash.Core.DataCon (DataCon)
8282
import Clash.Core.Literal (Literal)
8383
import Clash.Core.Name (Name (..))
84-
import {-# SOURCE #-} Clash.Core.Subst () -- instance Eq/Ord Type
84+
import {-# SOURCE #-} Clash.Core.Subst (acmpTerm, aeqTerm) -- instance Eq/Ord Type
8585
import {-# SOURCE #-} Clash.Core.Type (Type)
8686
import Clash.Core.Var (Var, Id, TyVar)
8787
import Clash.Util (curLoc, thenCompare)
@@ -124,19 +124,31 @@ data TickInfo
124124
| NoDeDup
125125
-- ^ Do not deduplicate, i.e. /keep/, an expression inside a case-alternative;
126126
-- do not try to share expressions between multiple branches.
127-
deriving (Eq, Show, Generic, NFData, Binary)
127+
| Attributes Type Term
128+
-- ^ Synthesis attributes brough into scope by
129+
-- 'Clash.Annotations.SynthesisAttributes.annotateReg'
130+
deriving (Show, Generic, NFData, Binary)
131+
132+
instance Eq TickInfo where
133+
SrcSpan s1 == SrcSpan s2 = s1 == s2
134+
NameMod m1 t1 == NameMod m2 t2 = m1 == m2 && t1 == t2
135+
Attributes t1 a1 == Attributes t2 a2 = t1 == t2 && aeqTerm a1 a2
136+
_ == _ = False
128137

129138
instance Ord TickInfo where
130139
compare (SrcSpan s1) (SrcSpan s2) = leftmost_smallest s1 s2
131140
compare (NameMod m1 t1) (NameMod m2 t2) =
132141
compare m1 m2 `thenCompare` compare t1 t2
142+
compare (Attributes t1 a1) (Attributes t2 a2) =
143+
compare t1 t2 `thenCompare` acmpTerm a1 a2
133144
compare t1 t2 = compare (getRank t1) (getRank t2)
134145
where
135146
getRank :: TickInfo -> Word
136-
getRank SrcSpan{} = 0
137-
getRank NameMod{} = 1
138-
getRank DeDup = 2
139-
getRank NoDeDup = 3
147+
getRank SrcSpan{} = 0
148+
getRank NameMod{} = 1
149+
getRank DeDup = 2
150+
getRank NoDeDup = 3
151+
getRank Attributes {} = 4
140152

141153
-- | Tag to indicate which instance/register name modifier was used
142154
data NameMod

clash-lib/src/Clash/Core/TermLiteral.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -129,6 +129,7 @@ instance TermLiteral Word where
129129
instance TermLiteral Integer where
130130
termToData (Tick _ e) = termToData e
131131
termToData (Literal (IntegerLiteral n)) = Right n
132+
termToData (collectArgs -> (_, [Left (Literal (IntLiteral n))])) = Right n
132133
termToData (collectArgs -> (_, [Left (Literal (IntegerLiteral n))])) = Right n
133134
termToData t = Left t
134135

0 commit comments

Comments
 (0)