Skip to content

Commit 690978d

Browse files
committed
copilot-bluespec: Flip direction of interface inputs and outputs in Bluespec. Refs #677.
The current Bluespec backend leads to Verilog code that requires manual manipulations in order to work correctly. Specifically, Copilot externs, which are inputs to the Copilot monitoring system, are treated as _outputs_ in Verilog, and Copilot triggers, which can be considered outputs of the monitoring system, are treated as _inputs_. This is the opposite of the interface that we would like users to work with, and of what other backends generate (e.g., C99). This commit updates the internals of `copilot-bluespec` to flip the order in which generated Bluespec module interfaces declare their inputs and outputs. A module interface now represents each Copilot extern as a method of type `<ty> -> Action` (where `<ty>` is the type of the extern), as this directly translates to a Verilog input. Moreover, a module interface now represents trigger arguments as interface methods of type `<ty>_i`, where each `<ty>_i` is the type of each trigger argument. Each `<ty>_i` directly translates to a Verilog output. In addition to changing the module interface definitions, this also changes the generated modules that instantiate the new interfaces. One of the more notable changes is that all extern values are stored as a Bluespec `Wire` in the module internals, as this leads to compact Verilog code without adding any user-visible inputs or outputs. Every time a value is read from an extern, the corresponding `Wire` must be read from, which means that several parts of the module internals have been updated to reference these `Wire`s.
1 parent 2f8ae35 commit 690978d

File tree

3 files changed

+136
-31
lines changed

3 files changed

+136
-31
lines changed

copilot-bluespec/src/Copilot/Compile/Bluespec/CodeGen.hs

Lines changed: 117 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -14,12 +14,17 @@ module Copilot.Compile.Bluespec.CodeGen
1414
-- * Stream generators
1515
, mkGenFun
1616

17+
-- * External streams
18+
, mkExtWireDecln
19+
1720
-- * Monitor processing
18-
, mkStepRule
21+
, mkExtRule
1922
, mkTriggerRule
23+
, mkStepRule
2024

2125
-- * Module interface specifications
2226
, mkSpecIfcFields
27+
, mkSpecIfcRulesFields
2328
) where
2429

2530
-- External imports
@@ -50,6 +55,16 @@ mkGenFun name expr ty =
5055
nameId = BS.mkId BS.NoPos $ fromString $ lowercaseName name
5156
def = BS.CClause [] [] (transExpr expr)
5257

58+
-- | Bind a @Wire@ variable using @mkBypassWire@.
59+
mkExtWireDecln :: String -> Type a -> BS.CStmt
60+
mkExtWireDecln name ty =
61+
BS.CSBindT
62+
(BS.CPVar (BS.mkId BS.NoPos (fromString (wireName name))))
63+
Nothing
64+
[]
65+
(BS.CQType [] (tWire `BS.TAp` transType ty))
66+
(BS.CVar (BS.mkId BS.NoPos "mkBypassWire"))
67+
5368
-- | Bind a buffer variable and initialise it with the stream buffer.
5469
mkBuffDecln :: forall a. Id -> Type a -> [a] -> [BS.CStmt]
5570
mkBuffDecln sId ty xs =
@@ -133,44 +148,112 @@ mkAccessDecln sId ty xs =
133148

134149
-- | Define fields for a module interface containing a specification's trigger
135150
-- functions and external variables.
136-
mkSpecIfcFields :: [Trigger] -> [External] -> [BS.CField]
137-
mkSpecIfcFields triggers exts =
151+
mkSpecIfcFields :: [UniqueTrigger] -> [External] -> [BS.CField]
152+
mkSpecIfcFields uniqueTriggers exts =
153+
concatMap mkTriggerFields uniqueTriggers ++ map mkExtField exts
154+
where
155+
-- trigger_guard :: Bool
156+
-- trigger_arg0 :: arg_ty_0
157+
-- ...
158+
-- trigger_arg(n-1) :: arg_ty_(n-1)
159+
mkTriggerFields :: UniqueTrigger -> [BS.CField]
160+
mkTriggerFields (UniqueTrigger uniqueName (Trigger _name _ args)) =
161+
mkField (guardName uniqueName) [] BS.tBool
162+
: zipWith
163+
(\(UExpr arg _) argName -> mkField argName [] (transType arg))
164+
args
165+
(argNames uniqueName)
166+
167+
-- ext :: ty -> Action
168+
mkExtField :: External -> BS.CField
169+
mkExtField (External name ty) =
170+
mkField
171+
name
172+
[ BS.PIPrefixStr ""
173+
, BS.PIArgNames [BS.mkId BS.NoPos $ fromString $ lowercaseName name]
174+
]
175+
(BS.tArrow `BS.TAp` transType ty `BS.TAp` BS.tAction)
176+
177+
-- | Define fields for a module interface containing the actions to perform for
178+
-- a specification's trigger functions and external variables.
179+
mkSpecIfcRulesFields :: [Trigger] -> [External] -> [BS.CField]
180+
mkSpecIfcRulesFields triggers exts =
138181
map mkTriggerField triggers ++ map mkExtField exts
139182
where
140-
-- trigger :: args_1 -> ... -> args_n -> Action
183+
-- trigger_action :: arg_ty_0 -> ... -> arg_ty_(n-1) -> Action
141184
mkTriggerField :: Trigger -> BS.CField
142185
mkTriggerField (Trigger name _ args) =
143-
mkField name $
144-
foldr
145-
(\(UExpr arg _) res -> BS.tArrow `BS.TAp` transType arg `BS.TAp` res)
146-
BS.tAction
147-
args
186+
mkField
187+
(actionName name)
188+
[]
189+
(foldr
190+
(\(UExpr arg _) res -> BS.tArrow `BS.TAp` transType arg `BS.TAp` res)
191+
BS.tAction
192+
args)
148193

149-
-- ext :: Reg ty
194+
-- ext_action :: ActionValue ty
150195
mkExtField :: External -> BS.CField
151196
mkExtField (External name ty) =
152-
mkField name $ tReg `BS.TAp` transType ty
197+
mkField (actionName name) [] (BS.tActionValue `BS.TAp` transType ty)
198+
199+
-- | Define a rule for an external stream that performs an action on the most
200+
-- recently computed value from the stream.
201+
mkExtRule :: External -> BS.CRule
202+
mkExtRule (External name _) =
203+
-- rules
204+
-- "ext": when True ==>
205+
-- action
206+
-- extVal <- ifcRules.ext_action
207+
-- ifc.ext extVal
208+
BS.CRule
209+
[]
210+
(Just $ cLit $ BS.LString name)
211+
[ BS.CQFilter $ BS.CCon BS.idTrue []
212+
]
213+
(BS.Caction
214+
BS.NoPos
215+
[ BS.CSBind
216+
(BS.CPVar extValId)
217+
Nothing
218+
[]
219+
(BS.CSelect (BS.CVar ifcRulesArgId) extActionId)
220+
, BS.CSExpr Nothing $
221+
BS.CApply (BS.CSelect (BS.CVar ifcArgId) extId) [BS.CVar extValId]
222+
])
223+
where
224+
ifcArgId = BS.mkId BS.NoPos $ fromString ifcArgName
225+
ifcRulesArgId = BS.mkId BS.NoPos $ fromString ifcRulesArgName
226+
227+
extActionId = BS.mkId BS.NoPos $ fromString $ actionName name
228+
extId = BS.mkId BS.NoPos $ fromString name
229+
extValId = BS.mkId BS.NoPos $ fromString $ name ++ "Val"
153230

154-
-- | Define a rule for a trigger function.
231+
-- | Define a rule for a trigger function that performs an action when the rule
232+
-- fires.
155233
mkTriggerRule :: UniqueTrigger -> BS.CRule
156234
mkTriggerRule (UniqueTrigger uniqueName (Trigger name _ args)) =
235+
-- rules
236+
-- "trigger": when ifc.trigger_guard ==>
237+
-- ifcRules.trigger_action ifc.trigger_arg0
157238
BS.CRule
158239
[]
159240
(Just $ cLit $ BS.LString uniqueName)
160241
[ BS.CQFilter $
161-
BS.CVar $ BS.mkId BS.NoPos $
162-
fromString $ guardName uniqueName
242+
BS.CSelect
243+
(BS.CVar ifcArgId)
244+
(BS.mkId BS.NoPos $ fromString $ guardName uniqueName)
163245
]
164-
(BS.CApply nameExpr args')
246+
(BS.CApply actionNameExpr args')
165247
where
166248
ifcArgId = BS.mkId BS.NoPos $ fromString ifcArgName
249+
ifcRulesArgId = BS.mkId BS.NoPos $ fromString ifcRulesArgName
167250
-- Note that we use 'name' here instead of 'uniqueName', as 'name' is the
168251
-- name of the actual external function.
169-
nameId = BS.mkId BS.NoPos $ fromString $ lowercaseName name
170-
nameExpr = BS.CSelect (BS.CVar ifcArgId) nameId
252+
actionNameId = BS.mkId BS.NoPos $ fromString $ actionName name
253+
actionNameExpr = BS.CSelect (BS.CVar ifcRulesArgId) actionNameId
171254

172-
args' = take (length args) (map argCall (argNames uniqueName))
173-
argCall = BS.CVar . BS.mkId BS.NoPos . fromString
255+
args' = take (length args) (map argCall (argNames uniqueName))
256+
argCall = BS.CSelect (BS.CVar ifcArgId) . BS.mkId BS.NoPos . fromString
174257

175258
-- | Writes the @step@ rule that updates all streams.
176259
mkStepRule :: [Stream] -> Maybe BS.CRule
@@ -238,14 +321,15 @@ mkStructDecln x =
238321

239322
mkStructField :: Value a -> BS.CField
240323
mkStructField (Value ty field) =
241-
mkField (fieldName field) (transType ty)
324+
mkField (fieldName field) [] (transType ty)
242325

243-
-- | Write a field of a struct or interface, along with its type.
244-
mkField :: String -> BS.CType -> BS.CField
245-
mkField name ty =
326+
-- | Write a field of a struct or interface, along with its pragmas and type
327+
-- signature.
328+
mkField :: String -> [BS.IfcPragma] -> BS.CType -> BS.CField
329+
mkField name pragmas ty =
246330
BS.CField
247331
{ BS.cf_name = BS.mkId BS.NoPos $ fromString $ lowercaseName name
248-
, BS.cf_pragmas = Nothing
332+
, BS.cf_pragmas = Just pragmas
249333
, BS.cf_type = BS.CQType [] ty
250334
, BS.cf_default = []
251335
, BS.cf_orig_type = Nothing
@@ -260,3 +344,12 @@ tReg = BS.TCon $
260344
, BS.tcon_sort = BS.TIstruct (BS.SInterface [])
261345
[BS.id_write BS.NoPos, BS.id_read BS.NoPos]
262346
}
347+
348+
-- | The @Wire@ Bluespec type.
349+
tWire :: BS.CType
350+
tWire = BS.TCon $
351+
BS.TyCon
352+
{ BS.tcon_name = BS.mkId BS.NoPos "Wire"
353+
, BS.tcon_kind = Just (BS.Kfun BS.KStar BS.KStar)
354+
, BS.tcon_sort = BS.TItype 0 tReg
355+
}

copilot-bluespec/src/Copilot/Compile/Bluespec/Expr.hs

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -51,11 +51,8 @@ transExpr (Drop _ amount sid) =
5151
[BS.CLit $ BS.CLiteral BS.NoPos index]
5252

5353
transExpr (ExternVar _ name _) =
54-
let ifcArgId = BS.mkId BS.NoPos $ fromString ifcArgName in
5554
BS.CSelect
56-
(BS.CSelect
57-
(BS.CVar ifcArgId)
58-
(BS.mkId BS.NoPos $ fromString $ lowercaseName name))
55+
(BS.CVar $ BS.mkId BS.NoPos $ fromString $ wireName name)
5956
(BS.id_read BS.NoPos)
6057

6158
transExpr (Label _ _ e) = transExpr e -- ignore label

copilot-bluespec/src/Copilot/Compile/Bluespec/Name.hs

Lines changed: 18 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,11 @@
11
-- | Naming of variables and functions in Bluespec.
22
module Copilot.Compile.Bluespec.Name
3-
( argNames
3+
( actionName
4+
, argNames
45
, generatorName
56
, guardName
67
, ifcArgName
8+
, ifcRulesArgName
79
, indexName
810
, lowercaseName
911
, specIfcName
@@ -13,6 +15,7 @@ module Copilot.Compile.Bluespec.Name
1315
, streamElemName
1416
, streamName
1517
, uppercaseName
18+
, wireName
1619
) where
1720

1821
-- External imports
@@ -41,11 +44,14 @@ specTypesPkgName prefix = prefix ++ "Types"
4144
streamElemName :: Id -> Int -> String
4245
streamElemName sId n = streamName sId ++ "_" ++ show n
4346

44-
-- | The name of the variable of type @<prefix>Ifc@. This is used to select
45-
-- trigger functions and external variables.
47+
-- | The name of a variable of type @<prefix>Ifc@.
4648
ifcArgName :: String
4749
ifcArgName = "ifc"
4850

51+
-- | The name of a variable of type @<prefix>RulesIfc@.
52+
ifcRulesArgName :: String
53+
ifcRulesArgName = "ifcRules"
54+
4955
-- | Create a Bluespec name that must start with an uppercase letter (e.g., a
5056
-- struct or interface name). If the supplied name already begins with an
5157
-- uppercase letter, this function returns the name unchanged. Otherwise, this
@@ -86,6 +92,15 @@ generatorName sId = streamName sId ++ "_gen"
8692
guardName :: String -> String
8793
guardName name = lowercaseName name ++ "_guard"
8894

95+
-- | Turn the name of a trigger of external stream into the name of a method
96+
-- that performs a Bluespec @Action@.
97+
actionName :: String -> String
98+
actionName name = lowercaseName name ++ "_action"
99+
100+
-- | Turn the name of an external stream into a Bluespec @Wire@.
101+
wireName :: String -> String
102+
wireName name = lowercaseName name ++ "_wire"
103+
89104
-- | Turn a trigger name into a an trigger argument name.
90105
argName :: String -> Int -> String
91106
argName name n = lowercaseName name ++ "_arg" ++ show n

0 commit comments

Comments
 (0)