@@ -57,13 +57,11 @@ compileWith bsSettings prefix spec
5757
5858 | otherwise
5959 = do let typesBsFile = render $ pPrint $ compileTypesBS bsSettings prefix spec
60- ifcBsFile = render $ pPrint $ compileIfcBS bsSettings prefix spec
6160 bsFile = render $ pPrint $ compileBS bsSettings prefix spec
6261
6362 let dir = bluespecSettingsOutputDirectory bsSettings
6463 createDirectoryIfMissing True dir
6564 writeFile (dir </> specTypesPkgName prefix ++ " .bs" ) typesBsFile
66- writeFile (dir </> specIfcPkgName prefix ++ " .bs" ) ifcBsFile
6765 writeFile (dir </> " bs_fp.c" ) copilotBluespecFloatingPointC
6866 writeFile (dir </> " BluespecFP.bsv" ) copilotBluespecFloatingPointBSV
6967 writeFile (dir </> prefix ++ " .bs" ) bsFile
@@ -93,86 +91,147 @@ compile :: String -> Spec -> IO ()
9391compile = compileWith mkDefaultBluespecSettings
9492
9593-- | Generate a @<prefix>.bs@ file from a 'Spec'. This is the main payload of
96- -- the Bluespec backend.
97- --
98- -- The generated Bluespec file will import a handful of files from the standard
99- -- library, as well as the following generated files:
100- --
101- -- * @<prefix>Ifc.bs@, which defines the interface containing the trigger
102- -- functions and external variables.
103- --
104- -- * @<prefix>Types.bs@, which defines any structs used in the 'Spec'.
105- --
106- -- It will also generate a @mk<prefix> :: Module <prefix>Ifc -> Module Empty@
107- -- function, which defines the module structure for this 'Spec'. The
108- -- @mk<prefix>@ function has the following structure:
109- --
110- -- * First, bind the argument of type @Module <prefix>Ifc@ so that trigger
111- -- functions can be invoked and external variables can be used.
112- --
113- -- * Next, declare stream buffers and indices.
114- --
115- -- * Next, declare generator functions for streams, accessor functions for
116- -- streams, and guard functions for triggers.
117- --
118- -- * Next, declare rules for each trigger function.
119- --
120- -- * Finally, declare a single rule that updates the stream buffers and
121- -- indices.
94+ -- the Bluespec backend. See the @copilot-bluespec/DESIGN.md@ document for a
95+ -- high-level description of what this file contains.
12296compileBS :: BluespecSettings -> String -> Spec -> BS. CPackage
12397compileBS _bsSettings prefix spec =
12498 BS. CPackage
12599 (BS. mkId BS. NoPos (fromString prefix))
126100 (Right [] )
127101 (stdLibImports ++ genImports)
128102 []
129- [moduleDef]
103+ [ ifcDef
104+ , mkModuleDefPragma
105+ , mkModuleDef
106+ , ifcRulesDef
107+ , mkModuleRulesDef
108+ , addModuleRulesDef
109+ ]
130110 []
131111 where
132112 -- import <prefix>Types
133- -- import <prefix>Ifc
134113 genImports :: [BS. CImport ]
135114 genImports =
136115 [ BS. CImpId False $ BS. mkId BS. NoPos $ fromString
137116 $ specTypesPkgName prefix
138- , BS. CImpId False $ BS. mkId BS. NoPos $ fromString
139- $ specIfcPkgName prefix
140117 , BS. CImpId False $ BS. mkId BS. NoPos " BluespecFP"
141118 ]
142119
143- moduleDef :: BS. CDefn
144- moduleDef = BS. CValueSign $
120+ -- interface <prefix>Ifc {-# always_ready, always_enabled #-} =
121+ -- ...
122+ ifcDef :: BS. CDefn
123+ ifcDef = BS. Cstruct
124+ True
125+ (BS. SInterface [BS. PIAlwaysRdy , BS. PIAlwaysEnabled ])
126+ (BS. IdK ifcId)
127+ [] -- No type variables
128+ ifcFields
129+ [] -- No derived instances
130+
131+ -- {-# properties mkFibs = { verilog } #-}
132+ mkModuleDefPragma :: BS. CDefn
133+ mkModuleDefPragma = BS. CPragma $ BS. Pproperties mkModuleDefId [BS. PPverilog ]
134+
135+ -- mk<prefix> :: Module <prefix>Ifc
136+ -- mk<prefix> =
137+ -- module
138+ -- ...
139+ mkModuleDef :: BS. CDefn
140+ mkModuleDef = BS. CValueSign $
145141 BS. CDef
146- (BS. mkId BS. NoPos $ fromString $ " mk" ++ prefix)
147- -- :: Module <prefix>Ifc -> Module Empty
142+ mkModuleDefId
148143 (BS. CQType
149144 []
150- (BS. tArrow
151- `BS. TAp ` (BS. tModule `BS. TAp ` ifcTy)
152- `BS. TAp ` (BS. tModule `BS. TAp ` emptyTy)))
153- [ BS. CClause [BS. CPVar ifcModId] [] $
154- BS. Cmodule BS. NoPos $
155- BS. CMStmt
156- (BS. CSBind (BS. CPVar ifcArgId) Nothing [] (BS. CVar ifcModId))
157- : map BS. CMStmt mkGlobals ++
158- [ BS. CMStmt $ BS. CSletrec genFuns
159- , BS. CMrules $ BS. Crules [] rules
160- ]
145+ (BS. tModule `BS. TAp ` ifcTy))
146+ [ BS. CClause [] [] $
147+ BS. Cmodule BS. NoPos $
148+ map BS. CMStmt (mkExtWires ++ mkGlobals) ++
149+ -- language-bluespec's pretty-printer will error if it
150+ -- encounters a CSletrec with an empty list of definitions, so
151+ -- avoid generating a CSletrec if there are no streams.
152+ [ BS. CMStmt $ BS. CSletrec genFuns | not (null genFuns) ] ++
153+ [ BS. CMrules $ BS. Crules [] $ maybeToList $ mkStepRule streams
154+ , BS. CMinterface $
155+ BS. Cinterface
156+ BS. NoPos
157+ (Just ifcId)
158+ ifcMethodImpls
159+ ]
161160 ]
162161
163- ifcArgId = BS. mkId BS. NoPos $ fromString ifcArgName
164- ifcModId = BS. mkId BS. NoPos " ifcMod"
165-
166- rules :: [BS. CRule ]
167- rules = map mkTriggerRule uniqueTriggers ++ maybeToList (mkStepRule streams)
162+ -- interface <prefix>RulesIfc =
163+ -- ...
164+ ifcRulesDef :: BS. CDefn
165+ ifcRulesDef =
166+ BS. Cstruct
167+ True
168+ (BS. SInterface [] )
169+ (BS. IdK ifcRulesId)
170+ [] -- No type variables
171+ ifcRulesFields
172+ [] -- No derived instances
173+
174+ -- mk<prefix>Rules :: <prefix>Ifc -> <prefix>RulesIfc -> Rules
175+ -- mk<prefix>Rules ifc ifcRules =
176+ -- rules
177+ -- ...
178+ mkModuleRulesDef :: BS. CDefn
179+ mkModuleRulesDef =
180+ BS. CValueSign $
181+ BS. CDef
182+ mkModuleRulesDefId
183+ (BS. CQType
184+ []
185+ (BS. tArrow `BS. TAp ` ifcTy `BS. TAp `
186+ (BS. tArrow `BS. TAp ` ifcRulesTy `BS. TAp ` BS. tRules)))
187+ [BS. CClause
188+ (map BS. CPVar [ifcArgId, ifcRulesArgId])
189+ []
190+ (BS. Crules
191+ []
192+ (map mkTriggerRule uniqueTriggers ++ map mkExtRule exts))]
193+
194+ -- add<prefix>Rules :: <prefix>Ifc -> <prefix>RulesIfc -> Module Empty
195+ -- add<prefix>Rules ifc ifcRules = addRules (mk<prefix>Rules ifc ifcRules)
196+ addModuleRulesDef :: BS. CDefn
197+ addModuleRulesDef =
198+ BS. CValueSign $
199+ BS. CDef
200+ addModuleRulesDefId
201+ (BS. CQType
202+ []
203+ (BS. tArrow `BS. TAp ` ifcTy `BS. TAp `
204+ (BS. tArrow `BS. TAp ` ifcRulesTy `BS. TAp `
205+ (BS. tModule `BS. TAp ` emptyTy))))
206+ [BS. CClause
207+ (map BS. CPVar [ifcArgId, ifcRulesArgId])
208+ []
209+ (BS. CApply
210+ (BS. CVar (BS. idAddRules BS. NoPos ))
211+ [BS. CApply
212+ (BS. CVar mkModuleRulesDefId)
213+ (map BS. CVar [ifcArgId, ifcRulesArgId])])]
214+
215+ mkModuleDefId =
216+ BS. mkId BS. NoPos $ fromString $ " mk" ++ prefix
217+ mkModuleRulesDefId =
218+ BS. mkId BS. NoPos $ fromString $ " mk" ++ prefix ++ " Rules"
219+ addModuleRulesDefId =
220+ BS. mkId BS. NoPos $ fromString $ " add" ++ prefix ++ " Rules"
168221
169222 streams = specStreams spec
170223 triggers = specTriggers spec
171224 uniqueTriggers = mkUniqueTriggers triggers
172225 exts = gatherExts streams triggers
173226
227+ -- Remove duplicates due to multiple guards for the same trigger.
228+ triggersNoDups = nubBy compareTrigger triggers
229+
230+ ifcArgId = BS. mkId BS. NoPos $ fromString ifcArgName
231+ ifcRulesArgId = BS. mkId BS. NoPos $ fromString ifcRulesArgName
232+
174233 ifcId = BS. mkId BS. NoPos $ fromString $ specIfcName prefix
175- ifcFields = mkSpecIfcFields triggers exts
234+ ifcFields = mkSpecIfcFields uniqueTriggers exts
176235 ifcTy = BS. TCon (BS. TyCon
177236 { BS. tcon_name = ifcId
178237 , BS. tcon_kind = Just BS. KStar
@@ -181,81 +240,85 @@ compileBS _bsSettings prefix spec =
181240 (map BS. cf_name ifcFields)
182241 })
183242
243+ ifcRulesId = BS. mkId BS. NoPos $ fromString $ specIfcRulesName prefix
244+ ifcRulesFields = mkSpecIfcRulesFields triggersNoDups exts
245+ ifcRulesTy =
246+ BS. TCon $
247+ BS. TyCon
248+ { BS. tcon_name = ifcRulesId
249+ , BS. tcon_kind = Just BS. KStar
250+ , BS. tcon_sort =
251+ BS. TIstruct (BS. SInterface [] ) (map BS. cf_name ifcRulesFields)
252+ }
253+
184254 emptyTy = BS. TCon (BS. TyCon
185255 { BS. tcon_name = BS. idEmpty
186256 , BS. tcon_kind = Just BS. KStar
187257 , BS. tcon_sort = BS. TIstruct (BS. SInterface [] ) []
188258 })
189259
260+ -- Bind @Wire@ variables for each extern stream.
261+ mkExtWires :: [BS. CStmt ]
262+ mkExtWires = map extWireStmt exts
263+ where
264+ extWireStmt :: External -> BS. CStmt
265+ extWireStmt (External name ty) = mkExtWireDecln name ty
266+
190267 -- Make buffer and index declarations for streams.
191268 mkGlobals :: [BS. CStmt ]
192269 mkGlobals = concatMap buffDecln streams ++ map indexDecln streams
193270 where
194271 buffDecln (Stream sId buff _ ty) = mkBuffDecln sId ty buff
195272 indexDecln (Stream sId _ _ _ ) = mkIndexDecln sId
196273
197- -- Make generator functions, including trigger arguments .
274+ -- Make generator functions for streams .
198275 genFuns :: [BS. CDefl ]
199- genFuns = map accessDecln streams
200- ++ map streamGen streams
201- ++ concatMap triggerGen uniqueTriggers
276+ genFuns = map accessDecln streams ++ map streamGen streams
202277 where
203278 accessDecln :: Stream -> BS. CDefl
204279 accessDecln (Stream sId buff _ ty) = mkAccessDecln sId ty buff
205280
206281 streamGen :: Stream -> BS. CDefl
207282 streamGen (Stream sId _ expr ty) = mkGenFun (generatorName sId) expr ty
208283
209- triggerGen :: UniqueTrigger -> [BS. CDefl ]
210- triggerGen (UniqueTrigger uniqueName (Trigger _name guard args)) =
211- guardDef : argDefs
284+ -- Make interface methods for @<prefix>Ifc@.
285+ ifcMethodImpls :: [BS. CDefl ]
286+ ifcMethodImpls =
287+ concatMap triggerMethodImpls uniqueTriggers
288+ ++ map extMethodImpl exts
289+ where
290+ -- interface
291+ -- ext val = ext_wire := val
292+ extMethodImpl :: External -> BS. CDefl
293+ extMethodImpl (External name _) =
294+ let valId = BS. mkId BS. NoPos " val" in
295+ BS. CLValue
296+ (BS. mkId BS. NoPos (fromString name))
297+ [BS. CClause
298+ [BS. CPVar valId]
299+ []
300+ (BS. Cwrite
301+ BS. NoPos
302+ (BS. CVar (BS. mkId BS. NoPos (fromString (wireName name))))
303+ (BS. CVar valId))]
304+ []
305+
306+ -- interface
307+ -- trig_guard = ...
308+ -- trig_arg0 = ...
309+ -- ...
310+ -- trig_arg(n-1) = ...
311+ triggerMethodImpls :: UniqueTrigger -> [BS. CDefl ]
312+ triggerMethodImpls uniqueTrigger = guardDef : argDefs
212313 where
314+ UniqueTrigger uniqueName (Trigger _name guard args) = uniqueTrigger
315+
213316 guardDef = mkGenFun (guardName uniqueName) guard Bool
214317 argDefs = map argGen (zip (argNames uniqueName) args)
215318
216319 argGen :: (String , UExpr ) -> BS. CDefl
217320 argGen (argName, UExpr ty expr) = mkGenFun argName expr ty
218321
219- -- | Generate a @<prefix>Ifc.bs@ file from a 'Spec'. This contains the
220- -- definition of the @<prefix>Ifc@ interface, which declares the types of all
221- -- trigger functions and external variables. This is put in a separate file so
222- -- that larger applications can use it separately.
223- compileIfcBS :: BluespecSettings -> String -> Spec -> BS. CPackage
224- compileIfcBS _bsSettings prefix spec =
225- BS. CPackage
226- ifcPkgId
227- (Right [] )
228- (stdLibImports ++ genImports)
229- []
230- [ifcDef]
231- []
232- where
233- -- import <prefix>Types
234- genImports :: [BS. CImport ]
235- genImports =
236- [ BS. CImpId False $ BS. mkId BS. NoPos $ fromString
237- $ specTypesPkgName prefix
238- ]
239-
240- ifcId = BS. mkId BS. NoPos $ fromString $ specIfcName prefix
241- ifcPkgId = BS. mkId BS. NoPos $ fromString $ specIfcPkgName prefix
242- ifcFields = mkSpecIfcFields triggers exts
243-
244- streams = specStreams spec
245- exts = gatherExts streams triggers
246-
247- -- Remove duplicates due to multiple guards for the same trigger.
248- triggers = nubBy compareTrigger (specTriggers spec)
249-
250- ifcDef :: BS. CDefn
251- ifcDef = BS. Cstruct
252- True
253- (BS. SInterface [] )
254- (BS. IdK ifcId)
255- [] -- No type variables
256- ifcFields
257- [] -- No derived instances
258-
259322-- | Generate a @<prefix>Types.bs@ file from a 'Spec'. This declares the types
260323-- of any structs used by the Copilot specification. This is put in a separate
261324-- file so that larger applications can more easily substitute their own struct
0 commit comments