mirror of https://github.com/zachjs/sv2v.git
support multi-dimensional instances
This commit is contained in:
parent
487685e0f0
commit
3cfd368bc2
|
|
@ -81,7 +81,7 @@ convertDescription interfaces modules (Part attrs extern Module lifetime name po
|
|||
where modport = (interfaceName, modportDecls)
|
||||
Nothing -> return ()
|
||||
_ -> return ()
|
||||
collectInterface (Instance part _ ident Nothing _) =
|
||||
collectInterface (Instance part _ ident [] _) =
|
||||
if Map.member part interfaces
|
||||
then tell (Map.singleton ident part, Map.empty)
|
||||
else return ()
|
||||
|
|
@ -109,7 +109,7 @@ convertDescription interfaces modules (Part attrs extern Module lifetime name po
|
|||
mapper (dir, port, expr) =
|
||||
Variable dir mpt (ident ++ "_" ++ port) mprs Nil
|
||||
where (mpt, mprs) = lookupType interfaceItems expr
|
||||
mapInterface (Instance part params ident Nothing instancePorts) =
|
||||
mapInterface (Instance part params ident [] instancePorts) =
|
||||
-- expand modport port bindings
|
||||
case Map.lookup part interfaces of
|
||||
Just interface ->
|
||||
|
|
@ -118,8 +118,8 @@ convertDescription interfaces modules (Part attrs extern Module lifetime name po
|
|||
inlineInterface interface (ident, params, instancePorts)
|
||||
Nothing ->
|
||||
if Map.member part modules
|
||||
then Instance part params' ident Nothing expandedPorts
|
||||
else Instance part params ident Nothing instancePorts
|
||||
then Instance part params' ident [] expandedPorts
|
||||
else Instance part params ident [] instancePorts
|
||||
where
|
||||
expandedBindings = map (uncurry $ expandPortBinding part) (zip instancePorts [0..])
|
||||
expandedPorts = concatMap snd expandedBindings
|
||||
|
|
|
|||
|
|
@ -42,7 +42,10 @@ convert = map $ traverseDescriptions convertDescription
|
|||
convertDescription :: Description -> Description
|
||||
convertDescription part @ Part{} =
|
||||
scopedConversion traverseDeclM traverseModuleItemM traverseStmtM
|
||||
Map.empty part
|
||||
instances part'
|
||||
where
|
||||
(part', instances) = runState
|
||||
(traverseModuleItemsM traverseInstancesM part) Map.empty
|
||||
convertDescription other = other
|
||||
|
||||
-- collects and converts declarations with multiple packed dimensions
|
||||
|
|
@ -79,6 +82,19 @@ traverseTypeM t a ident = do
|
|||
fieldTypes' <- mapM (\x -> traverseTypeM x [] "") fieldTypes
|
||||
return $ zip fieldTypes' fieldNames
|
||||
|
||||
-- converts multi-dimensional instances
|
||||
traverseInstancesM :: ModuleItem -> State Info ModuleItem
|
||||
traverseInstancesM (Instance m p x rs l) = do
|
||||
rs' <- if length rs <= 1
|
||||
then return rs
|
||||
else do
|
||||
let t = Implicit Unspecified rs
|
||||
modify $ Map.insert x (t, [])
|
||||
let r1 : r2 : rest = rs
|
||||
return $ (combineRanges r1 r2) : rest
|
||||
return $ Instance m p x rs' l
|
||||
traverseInstancesM other = return other
|
||||
|
||||
-- combines two ranges into one flattened range
|
||||
combineRanges :: Range -> Range -> Range
|
||||
combineRanges r1 r2 = r
|
||||
|
|
|
|||
|
|
@ -42,9 +42,9 @@ traverseDeclM decl = do
|
|||
return decl'
|
||||
|
||||
traverseModuleItemM :: ModuleItem -> State Info ModuleItem
|
||||
traverseModuleItemM (Instance m p x r l) = do
|
||||
traverseModuleItemM (Instance m p x rs l) = do
|
||||
p' <- mapM paramBindingMapper p
|
||||
traverseExprsM traverseExprM $ Instance m p' x r l
|
||||
traverseExprsM traverseExprM $ Instance m p' x rs l
|
||||
where
|
||||
paramBindingMapper (param, Left t) = do
|
||||
t' <- traverseTypeExprsM substituteExprM t
|
||||
|
|
|
|||
|
|
@ -25,8 +25,8 @@ collectPortsM (Part _ _ _ _ name ports _) = tell $ Map.singleton name ports
|
|||
collectPortsM _ = return ()
|
||||
|
||||
mapInstance :: Ports -> ModuleItem -> ModuleItem
|
||||
mapInstance modulePorts (Instance m p x r bindings) =
|
||||
Instance m p x r $ concatMap expandBinding bindings
|
||||
mapInstance modulePorts (Instance m p x rs bindings) =
|
||||
Instance m p x rs $ concatMap expandBinding bindings
|
||||
where
|
||||
alreadyBound :: [Identifier]
|
||||
alreadyBound = map fst bindings
|
||||
|
|
|
|||
|
|
@ -598,11 +598,11 @@ traverseExprsM' strat exprMapper = moduleItemMapper
|
|||
then mapM stmtMapper stmts
|
||||
else return stmts
|
||||
return $ MIPackageItem $ Task lifetime f decls' stmts'
|
||||
moduleItemMapper (Instance m p x r l) = do
|
||||
moduleItemMapper (Instance m p x rs l) = do
|
||||
p' <- mapM paramBindingMapper p
|
||||
l' <- mapM portBindingMapper l
|
||||
r' <- mapM rangeMapper r
|
||||
return $ Instance m p' x r' l'
|
||||
rs' <- mapM rangeMapper rs
|
||||
return $ Instance m p' x rs' l'
|
||||
moduleItemMapper (Modport x l) =
|
||||
mapM modportDeclMapper l >>= return . Modport x
|
||||
moduleItemMapper (NInputGate kw d x lhs exprs) = do
|
||||
|
|
@ -915,9 +915,9 @@ traverseTypesM' strategy mapper item =
|
|||
fullMapper t >>= \t' -> return $ MIPackageItem $ Function l t' x d s
|
||||
miMapper (MIPackageItem (other @ (Task _ _ _ _))) =
|
||||
return $ MIPackageItem other
|
||||
miMapper (Instance m params x r p) = do
|
||||
miMapper (Instance m params x rs p) = do
|
||||
params' <- mapM mapParam params
|
||||
return $ Instance m params' x r p
|
||||
return $ Instance m params' x rs p
|
||||
where
|
||||
mapParam (i, Left t) =
|
||||
if strategy == IncludeParamTypes
|
||||
|
|
|
|||
|
|
@ -56,8 +56,8 @@ convertTypedef types =
|
|||
convertExpr (DimFn f v e) = DimFn f (convertTypeOrExpr v) e
|
||||
convertExpr other = other
|
||||
convertModuleItem :: ModuleItem -> ModuleItem
|
||||
convertModuleItem (Instance m params x r p) =
|
||||
Instance m (map mapParam params) x r p
|
||||
convertModuleItem (Instance m params x rs p) =
|
||||
Instance m (map mapParam params) x rs p
|
||||
where mapParam (i, v) = (i, convertTypeOrExpr v)
|
||||
convertModuleItem other = other
|
||||
|
||||
|
|
|
|||
|
|
@ -35,7 +35,7 @@ data ModuleItem
|
|||
| AlwaysC AlwaysKW Stmt
|
||||
| Assign AssignOption LHS Expr
|
||||
| Defparam LHS Expr
|
||||
| Instance Identifier [ParamBinding] Identifier (Maybe Range) [PortBinding]
|
||||
| Instance Identifier [ParamBinding] Identifier [Range] [PortBinding]
|
||||
| Genvar Identifier
|
||||
| Generate [GenItem]
|
||||
| Modport Identifier [ModportDecl]
|
||||
|
|
@ -66,11 +66,11 @@ instance Show ModuleItem where
|
|||
if null x
|
||||
then show a
|
||||
else printf "%s : %s" x (show a)
|
||||
show (Instance m params i r ports) =
|
||||
show (Instance m params i rs ports) =
|
||||
if null params
|
||||
then printf "%s %s%s%s;" m i rStr (showPorts ports)
|
||||
else printf "%s #%s %s%s%s;" m (showParams params) i rStr (showPorts ports)
|
||||
where rStr = maybe "" (\a -> showRanges [a] ++ " ") r
|
||||
then printf "%s %s%s%s;" m i rsStr (showPorts ports)
|
||||
else printf "%s #%s %s%s%s;" m (showParams params) i rsStr (showPorts ports)
|
||||
where rsStr = if null rs then "" else tail $ showRanges rs
|
||||
|
||||
showPorts :: [PortBinding] -> String
|
||||
showPorts ports = indentedParenList $ map showPort ports
|
||||
|
|
|
|||
|
|
@ -154,7 +154,7 @@ asElabTask :: [DeclToken] -> [ModuleItem]
|
|||
asElabTask [DTIdent _ name, DTInstance _ args] =
|
||||
if name == "$info"
|
||||
then [] -- just drop them for simplicity
|
||||
else [Instance "ThisModuleDoesNotExist" [] name' Nothing args]
|
||||
else [Instance "ThisModuleDoesNotExist" [] name' [] args]
|
||||
where name' = "__sv2v_elab_" ++ tail name
|
||||
asElabTask [DTIdent pos name] =
|
||||
asElabTask [DTIdent pos name, DTInstance pos []]
|
||||
|
|
@ -172,16 +172,19 @@ parseDTsAsIntantiations (DTIdent _ name : tokens) =
|
|||
step :: [DeclToken] -> [ModuleItem]
|
||||
step [] = error $ "unexpected end of instantiation list: " ++ (show tokens)
|
||||
step toks =
|
||||
Instance name params x mr p : follow
|
||||
case (init inst, last inst) of
|
||||
(DTIdent _ x : ranges, DTInstance _ p) ->
|
||||
Instance name params x rs p : follow
|
||||
where rs = map asRange ranges
|
||||
_ -> failure
|
||||
where
|
||||
(inst, toks') = span (not . isComma) toks
|
||||
(x, mr, p) = case inst of
|
||||
[DTIdent _ a, DTRange _ (NonIndexed, s), DTInstance _ b] ->
|
||||
(a, Just s , b)
|
||||
[DTIdent _ a, DTInstance _ b] -> (a, Nothing, b)
|
||||
_ -> error $ "unrecognized instantiation of " ++ name
|
||||
follow = if null toks' then [] else step (tail toks')
|
||||
asRange :: DeclToken -> Range
|
||||
asRange (DTRange _ (NonIndexed, s)) = s
|
||||
asRange _ = failure
|
||||
failure = error $ "unrecognized instantiation of " ++ name
|
||||
++ ": " ++ show inst
|
||||
follow = x `seq` if null toks' then [] else step (tail toks')
|
||||
(params, rest) =
|
||||
case head tokens of
|
||||
DTParams _ ps -> (ps, tail tokens)
|
||||
|
|
|
|||
|
|
@ -0,0 +1,14 @@
|
|||
module Example;
|
||||
parameter FOO = 1;
|
||||
initial $display("%0d", FOO);
|
||||
endmodule
|
||||
|
||||
module top;
|
||||
Example e[2:0][4:5]();
|
||||
defparam e[0][5].FOO = 1;
|
||||
defparam e[0][4].FOO = 2;
|
||||
defparam e[1][5].FOO = 4;
|
||||
defparam e[1][4].FOO = 8;
|
||||
defparam e[2][5].FOO = 16;
|
||||
defparam e[2][4].FOO = 32;
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,14 @@
|
|||
module Example;
|
||||
parameter FOO = 1;
|
||||
initial $display("%0d", FOO);
|
||||
endmodule
|
||||
|
||||
module top;
|
||||
Example e[5:0]();
|
||||
defparam e[0].FOO = 1;
|
||||
defparam e[1].FOO = 2;
|
||||
defparam e[2].FOO = 4;
|
||||
defparam e[3].FOO = 8;
|
||||
defparam e[4].FOO = 16;
|
||||
defparam e[5].FOO = 32;
|
||||
endmodule
|
||||
Loading…
Reference in New Issue