@@ -10,7 +10,6 @@ Stability : experimental
1010{-# Language OverloadedStrings #-}
1111{-# Language RecordWildCards #-}
1212{-# Language ViewPatterns #-}
13- {-# Language LambdaCase #-}
1413{-# Language MultiWayIf #-}
1514{-# Language TupleSections #-}
1615{-# Language ScopedTypeVariables #-}
@@ -93,62 +92,62 @@ convertYosysIR ::
9392 SC. SharedContext ->
9493 YosysIR ->
9594 IO (Map Text ConvertedModule )
96- convertYosysIR sc ir = do
97- let mg = yosysIRModgraph ir
98- let sorted = reverseTopSort $ mg ^. modgraphGraph
99- foldM
100- (\ env v -> do
101- let (m, nm, _) = mg ^. modgraphNodeFromVertex $ v
102- cm <- convertModule sc env m
103- _ <- validateTerm sc (" translating the combinational circuit \" " <> nm <> " \" " ) $ cm ^. convertedModuleTerm
104- n <- Nonce. freshNonce Nonce. globalNonceGenerator
105- let frag = Text. pack . show $ Nonce. indexValue n
106- let uri = URI. URI
107- { URI. uriScheme = URI. mkScheme " yosys"
108- , URI. uriAuthority = Left True
109- , URI. uriPath = (False ,) <$> mapM URI. mkPathPiece (nm NE. :| [] )
110- , URI. uriQuery = []
111- , URI. uriFragment = URI. mkFragment frag
112- }
113- let ni = SC. ImportedName uri [nm]
114- tc <- SC. scDefineConstant sc ni (cm ^. convertedModuleTerm) (cm ^. convertedModuleType)
115- let cm' = cm { _convertedModuleTerm = tc }
116- pure $ Map. insert nm cm' env
117- )
118- Map. empty
119- sorted
95+ convertYosysIR sc ir =
96+ do let mg = yosysIRModgraph ir
97+ let sorted = reverseTopSort $ mg ^. modgraphGraph
98+ foldM
99+ (\ env v ->
100+ do let (m, nm, _) = mg ^. modgraphNodeFromVertex $ v
101+ cm <- convertModule sc env m
102+ _ <- validateTerm sc (" translating the combinational circuit \" " <> nm <> " \" " ) $ cm ^. convertedModuleTerm
103+ n <- Nonce. freshNonce Nonce. globalNonceGenerator
104+ let frag = Text. pack . show $ Nonce. indexValue n
105+ let uri = URI. URI
106+ { URI. uriScheme = URI. mkScheme " yosys"
107+ , URI. uriAuthority = Left True
108+ , URI. uriPath = (False ,) <$> mapM URI. mkPathPiece (nm NE. :| [] )
109+ , URI. uriQuery = []
110+ , URI. uriFragment = URI. mkFragment frag
111+ }
112+ let ni = SC. ImportedName uri [nm]
113+ tc <- SC. scDefineConstant sc ni (cm ^. convertedModuleTerm) (cm ^. convertedModuleType)
114+ let cm' = cm { _convertedModuleTerm = tc }
115+ pure $ Map. insert nm cm' env
116+ )
117+ Map. empty
118+ sorted
120119
121120-- | Given a Yosys IR, construct a map from module names to TypedTerms
122121yosysIRToTypedTerms ::
123122 SC. SharedContext ->
124123 YosysIR ->
125124 IO (Map Text SC. TypedTerm )
126- yosysIRToTypedTerms sc ir = do
127- env <- convertYosysIR sc ir
128- pure . flip fmap env $ \ cm ->
129- SC. TypedTerm
130- (SC. TypedTermSchema $ C. tMono $ cm ^. convertedModuleCryptolType)
131- $ cm ^. convertedModuleTerm
125+ yosysIRToTypedTerms sc ir =
126+ do env <- convertYosysIR sc ir
127+ pure $ flip fmap env $ \ cm ->
128+ SC. TypedTerm
129+ (SC. TypedTermSchema $ C. tMono $ cm ^. convertedModuleCryptolType)
130+ $ cm ^. convertedModuleTerm
132131
133132-- | Given a Yosys IR, construct a SAWCore record containing terms for each module
134133yosysIRToRecordTerm ::
135134 SC. SharedContext ->
136135 YosysIR ->
137136 IO SC. TypedTerm
138- yosysIRToRecordTerm sc ir = do
139- env <- convertYosysIR sc ir
140- record <- cryptolRecord sc $ view convertedModuleTerm <$> env
141- let cty = C. tRec . C. recordFromFields $ (\ (nm, cm) -> (C. mkIdent nm, cm ^. convertedModuleCryptolType)) <$> Map. assocs env
142- let tt = SC. TypedTerm (SC. TypedTermSchema $ C. tMono cty) record
143- pure tt
137+ yosysIRToRecordTerm sc ir =
138+ do env <- convertYosysIR sc ir
139+ record <- cryptolRecord sc $ view convertedModuleTerm <$> env
140+ let cty = C. tRec . C. recordFromFields $ (\ (nm, cm) -> (C. mkIdent nm, cm ^. convertedModuleCryptolType)) <$> Map. assocs env
141+ let tt = SC. TypedTerm (SC. TypedTermSchema $ C. tMono cty) record
142+ pure tt
144143
145144-- | Given a Yosys IR, construct a value representing a specific module with all submodules inlined
146145yosysIRToSequential ::
147146 SC. SharedContext ->
148147 YosysIR ->
149148 Text ->
150149 IO YosysSequential
151- yosysIRToSequential sc ir nm = do
150+ yosysIRToSequential sc ir nm =
152151 case Map. lookup nm $ ir ^. yosysModules of
153152 Nothing -> throw . YosysError $ mconcat
154153 [ " Could not find module: "
@@ -167,12 +166,12 @@ yosysIRToSequential sc ir nm = do
167166-- Each HDL module is in turn represented by a function from a record
168167-- of input port values to a record of output port values.
169168yosys_import :: FilePath -> TopLevel SC. TypedTerm
170- yosys_import path = do
171- sc <- getSharedContext
172- ir <- liftIO $ loadYosysIR path
173- tt <- liftIO $ yosysIRToRecordTerm sc ir
174- _ <- liftIO $ validateTerm sc " translating combinational circuits" $ SC. ttTerm tt
175- pure tt
169+ yosys_import path =
170+ do sc <- getSharedContext
171+ ir <- liftIO $ loadYosysIR path
172+ tt <- liftIO $ yosysIRToRecordTerm sc ir
173+ _ <- liftIO $ validateTerm sc " translating combinational circuits" $ SC. ttTerm tt
174+ pure tt
176175
177176-- | Proves equality between a combinational HDL module and a
178177-- specification. Note that terms derived from HDL modules are first
@@ -187,31 +186,32 @@ yosys_verify ::
187186 [YosysTheorem ] {- ^ Overrides to apply -} ->
188187 ProofScript () ->
189188 TopLevel YosysTheorem
190- yosys_verify ymod preconds other specs tactic = do
191- sc <- getSharedContext
192- newmod <- liftIO $ foldM (flip $ applyOverride sc)
193- (SC. ttTerm ymod)
194- specs
195- mpc <- case preconds of
196- [] -> pure Nothing
197- (pc: pcs) -> do
198- t <- foldM (\ a b -> liftIO $ SC. scAnd sc a b) (SC. ttTerm pc) (SC. ttTerm <$> pcs)
199- pure . Just $ SC. TypedTerm (SC. ttType pc) t
200- thm <- liftIO $ buildTheorem sc ymod newmod mpc other
201- prop <- liftIO $ theoremProp sc thm
202- _ <- Builtins. provePrintPrim tactic prop
203- pure thm
189+ yosys_verify ymod preconds other specs tactic =
190+ do sc <- getSharedContext
191+ newmod <- liftIO $ foldM (flip $ applyOverride sc)
192+ (SC. ttTerm ymod)
193+ specs
194+ mpc <-
195+ case preconds of
196+ [] -> pure Nothing
197+ (pc: pcs) ->
198+ do t <- foldM (\ a b -> liftIO $ SC. scAnd sc a b) (SC. ttTerm pc) (SC. ttTerm <$> pcs)
199+ pure . Just $ SC. TypedTerm (SC. ttType pc) t
200+ thm <- liftIO $ buildTheorem sc ymod newmod mpc other
201+ prop <- liftIO $ theoremProp sc thm
202+ _ <- Builtins. provePrintPrim tactic prop
203+ pure thm
204204
205205-- | Import a single sequential HDL module. N.B. SAW expects the
206206-- sequential module to exist entirely within a single Yosys module.
207207yosys_import_sequential ::
208208 Text {- ^ Name of the HDL module -} ->
209209 FilePath {- ^ Path to the Yosys JSON file -} ->
210210 TopLevel YosysSequential
211- yosys_import_sequential nm path = do
212- sc <- getSharedContext
213- ir <- liftIO $ loadYosysIR path
214- liftIO $ yosysIRToSequential sc ir nm
211+ yosys_import_sequential nm path =
212+ do sc <- getSharedContext
213+ ir <- liftIO $ loadYosysIR path
214+ liftIO $ yosysIRToSequential sc ir nm
215215
216216-- | Extracts a term from the given sequential module with the state
217217-- eliminated by iterating the term over the given concrete number of
@@ -223,23 +223,23 @@ yosys_extract_sequential ::
223223 YosysSequential ->
224224 Integer {- ^ Number of cycles to iterate term -} ->
225225 TopLevel SC. TypedTerm
226- yosys_extract_sequential s n = do
227- sc <- getSharedContext
228- tt <- liftIO $ composeYosysSequential sc s n
229- _ <- liftIO $ validateTerm sc " composing a sequential term" $ SC. ttTerm tt
230- pure tt
226+ yosys_extract_sequential s n =
227+ do sc <- getSharedContext
228+ tt <- liftIO $ composeYosysSequential sc s n
229+ _ <- liftIO $ validateTerm sc " composing a sequential term" $ SC. ttTerm tt
230+ pure tt
231231
232232-- | Like `yosys_extract_sequential`, but the resulting term has an
233233-- additional parameter to specify the initial state.
234234yosys_extract_sequential_with_state ::
235235 YosysSequential ->
236236 Integer {- ^ Number of cycles to iterate term -} ->
237237 TopLevel SC. TypedTerm
238- yosys_extract_sequential_with_state s n = do
239- sc <- getSharedContext
240- tt <- liftIO $ composeYosysSequentialWithState sc s n
241- _ <- liftIO $ validateTerm sc " composing a sequential term with state" $ SC. ttTerm tt
242- pure tt
238+ yosys_extract_sequential_with_state s n =
239+ do sc <- getSharedContext
240+ tt <- liftIO $ composeYosysSequentialWithState sc s n
241+ _ <- liftIO $ validateTerm sc " composing a sequential term with state" $ SC. ttTerm tt
242+ pure tt
243243
244244-- | Extracts a term from the given sequential module. This term has
245245-- explicit fields for the state of the circuit in the input and
@@ -254,7 +254,7 @@ yosys_verify_sequential_sally ::
254254 SC. TypedTerm {- ^ A boolean function of three parameters: an 8-bit cycle counter, a record of "fixed" inputs, and a record of circuit outputs -} ->
255255 [Text ] {- ^ Names of circuit inputs that are fixed -} ->
256256 TopLevel ()
257- yosys_verify_sequential_sally s path q fixed = do
258- sc <- getSharedContext
259- sym <- liftIO $ Common. newSAWCoreExprBuilder sc False
260- liftIO $ queryModelChecker sym sc s path q $ Set. fromList fixed
257+ yosys_verify_sequential_sally s path q fixed =
258+ do sc <- getSharedContext
259+ sym <- liftIO $ Common. newSAWCoreExprBuilder sc False
260+ liftIO $ queryModelChecker sym sc s path q $ Set. fromList fixed
0 commit comments