Commit 67466eaa by Zachary Snow

major interface conversion update

- module instances with modport bindings are now inlined
- support for modports in generate loops
- support for generic interfaces
- implied modport instance propagation
- add error message for interface instances missing port list
parent 5161a9e7
......@@ -6,397 +6,333 @@
module Convert.Interface (convert) where
import Data.List (isPrefixOf)
import Data.Maybe (mapMaybe)
import Control.Monad.Writer
import Control.Monad.State
import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
import Convert.Scoper
import Convert.Traverse
import Language.SystemVerilog.AST
type Idents = Set.Set Identifier
type Interface = ([Identifier], [ModuleItem])
type Interfaces = Map.Map Identifier Interface
type Module = ([Identifier], [(Identifier, Type)])
type Modules = Map.Map Identifier Module
type Instances = Map.Map Identifier Identifier
type Modports = Map.Map Identifier (Identifier, Identifier)
data PartInfo = PartInfo
{ pKind :: PartKW
, pPorts :: [Identifier]
, pItems :: [ModuleItem]
} deriving Eq
type PartInfos = Map.Map Identifier PartInfo
type ModportInstances = [(Identifier, (Identifier, Identifier))]
type ModportBinding = (Identifier, (Expr, Expr))
convert :: [AST] -> [AST]
convert =
map (filter $ not . isInterface) .
repeatedConverter
traverseFiles (collectDescriptionsM collectPart)
(map . convertDescription)
where
repeatedConverter :: [AST] -> [AST]
repeatedConverter files =
if files == files'
then files
else repeatedConverter files'
where
files' =
traverseFiles (collectDescriptionsM collectDesc)
(map . uncurry convertDescription)
files
-- we can only collect/map non-extern interfaces
collectDesc :: Description -> Writer (Interfaces, Modules) ()
collectDesc (orig @ (Part _ False kw _ name ports items)) = do
if kw == Interface
then when (all fullyResolved items) $
tell (Map.singleton name (ports, items), Map.empty)
else tell (Map.empty, Map.singleton name (params, decls))
where
params = map fst $ parameters items
decls = execWriter $
collectModuleItemsM (collectDeclsM collectDecl) orig
collectDecl :: Decl -> Writer [(Identifier, Type)] ()
collectDecl (Variable _ t ident _ _) =
tell [(ident, t)]
collectDecl _ = return ()
collectDesc _ = return ()
isInterface :: Description -> Bool
isInterface (Part _ False Interface _ _ _ items) =
all fullyResolved items
isInterface _ = False
-- returns whether a ModuleItem still contains TypeOf
fullyResolved :: ModuleItem -> Bool
fullyResolved =
not . any isTypeOf . execWriter .
collectNestedModuleItemsM collectModport
where
collectModport :: ModuleItem -> Writer [Type] ()
collectModport (Modport _ modportDecls) =
mapM collectModportDecl modportDecls >> return ()
collectModport _ = return ()
collectModportDecl :: ModportDecl -> Writer [Type] ()
collectModportDecl (_, _, t, _) = collectType t
collectType :: Type -> Writer [Type] ()
collectType t = tell [t]
isTypeOf TypeOf{} = True
isTypeOf _ = False
convertDescription :: Interfaces -> Modules -> Description -> Description
convertDescription interfaces modules (Part attrs extern Module lifetime name ports items) =
Part attrs extern Module lifetime name ports' items'
-- we can only collect/map non-extern interfaces and modules
collectPart :: Description -> Writer PartInfos ()
collectPart (Part _ False kw _ name ports items) =
tell $ Map.singleton name $ PartInfo kw ports items
collectPart _ = return ()
convertDescription :: PartInfos -> Description -> Description
convertDescription _ (Part _ _ Interface _ name _ _) =
PackageItem $ Decl $ CommentDecl $ "removed interface: " ++ name
convertDescription parts (Part attrs extern Module lifetime name ports items) =
if null $ extractModportInstances $ PartInfo Module ports items then
Part attrs extern Module lifetime name ports items'
else
PackageItem $ Decl $ CommentDecl $
"removed interface-using module: " ++ name
where
items' = map (flattenInstances instances modports) $
map (traverseNestedModuleItems expandInterface) items
ports' = concatMap convertPort ports
-- collect the interface type of all interface instances in this module
(instances, modports) = execWriter $ mapM
(collectNestedModuleItemsM collectInstanceM) items
collectInstanceM :: ModuleItem -> Writer (Instances, Modports) ()
collectInstanceM (MIPackageItem (Decl (Variable _ t ident _ _))) =
case t of
InterfaceT interfaceName (Just modportName) [] ->
when (Map.member interfaceName interfaces) $
writeModport interfaceName modportName
Alias interfaceName [] ->
when (Map.member interfaceName interfaces) $
writeModport interfaceName ""
_ -> return ()
items' = evalScoper return traverseModuleItemM return return name items
convertNested =
scopeModuleItemT return traverseModuleItemM return return
traverseModuleItemM :: ModuleItem -> Scoper [ModportDecl] ModuleItem
traverseModuleItemM (Modport modportName modportDecls) =
insertElem modportName modportDecls >> return (Generate [])
traverseModuleItemM (instanceItem @ (Instance _ _ _ [] _)) =
if maybePartInfo == Nothing then
return instanceItem
else if partKind == Interface then
-- inline instantiation of an interface
convertNested $ Generate $ map GenModuleItem $
inlineInstance [] []
partItems instanceName paramBindings portBindings
else if not $ null (extractModportInstances partInfo) then do
modports <- embedScopes (\l () -> l) ()
-- inline instantiation of a module
convertNested $ Generate $ map GenModuleItem $
inlineInstance
(modportBindings modports)
(modportSubstitutions modports)
partItems instanceName paramBindings portBindings
else
return instanceItem
where
writeModport :: Identifier -> Identifier ->
Writer (Instances, Modports) ()
writeModport interfaceName modportName =
tell (Map.empty, Map.singleton ident modport)
where modport = (interfaceName, modportName)
collectInstanceM (Instance part _ ident [] _) =
when (Map.member part interfaces) $
tell (Map.singleton ident part, Map.empty)
collectInstanceM _ = return ()
expandInterface :: ModuleItem -> ModuleItem
expandInterface (orig @ (MIPackageItem (Decl (Variable _ _ ident _ _)))) =
-- expand instantiation of a modport
if Map.member ident modports
then Generate $ map GenModuleItem $
filter shouldKeep interfaceItems ++ map makePortDecl
modportDecls
else orig
Instance part rawParamBindings instanceName [] rawPortBindings =
instanceItem
maybePartInfo = Map.lookup part parts
Just partInfo = maybePartInfo
PartInfo partKind partPorts partItems = partInfo
partParams = parameterNames partItems
paramBindings = resolveBindings partParams rawParamBindings
portBindings = resolveBindings partPorts rawPortBindings
modportInstances = extractModportInstances partInfo
modportBindings modports = mapMaybe
(inferModportBinding modports modportInstances) portBindings
modportSubstitutions modports = concatMap
(expandModportBinding modports) (modportBindings modports)
traverseModuleItemM other = return other
-- determines the underlying modport and interface instances associated
-- with the given port binding, if it is a modport binding
inferModportBinding :: Scopes [ModportDecl] -> ModportInstances ->
PortBinding -> Maybe ModportBinding
inferModportBinding _ _ ("", _) =
error "internal inferModportBinding invariant violated"
inferModportBinding modports modportInstances (portName, expr) =
if bindingIsModport then
-- provided specific instance modport
foundModport expr
else if bindingIsBundle && portIsBundle then
-- bundle bound to a generic bundle
foundModport expr
else if bindingIsBundle && not portIsBundle then
-- given entire interface, but just bound to a modport
foundModport $ Dot expr modportName
else
Nothing
where
Just (interfaceName, modportName) = Map.lookup ident modports
interfaceItems = prefixInterface ident $
snd $ lookupInterface interfaceName
modportDecls = lookupModport interfaceItems modportName
shouldKeep (MIPackageItem (Decl Param{})) = True
shouldKeep (MIPackageItem Task{}) = True
shouldKeep (MIPackageItem Function{}) = True
shouldKeep _ = False
makePortDecl :: ModportDecl -> ModuleItem
makePortDecl (dir, port, typ, _) =
MIPackageItem $ Decl $ Variable dir typ port' [] Nil
where port' = if null modportName
then port
else ident ++ '_' : port
expandInterface (Instance part params ident [] instancePorts) =
-- expand modport port bindings
case Map.lookup part interfaces of
Just interface ->
-- inline instantiation of an interface
Generate $ map GenModuleItem $
inlineInterface interface (ident, params, instancePorts)
Nothing ->
if Map.member part modules
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
Just (moduleParamNames, _) = Map.lookup part modules
addedParams = concatMap fst expandedBindings
paramsNamed = resolveParams moduleParamNames params
params' =
if null addedParams
then params
else paramsNamed ++ addedParams
expandInterface other = other
expandPortBinding :: Identifier -> PortBinding -> Int -> ([ParamBinding], [PortBinding])
expandPortBinding moduleName ("", binding) idx =
case Map.lookup moduleName modules of
Nothing -> error $ "could not find module: " ++ moduleName
Just (_, decls) ->
if idx < length decls
then expandPortBinding moduleName
(fst $ decls !! idx, binding) idx
else error $ "could not infer port for "
++ show binding ++ " in module " ++ show moduleName
expandPortBinding _ (origBinding @ (portName, Dot (Ident instanceName) modportName)) _ =
-- expand instance modport bound to a modport
if Map.member instanceName instances
then expandPortBinding' interfaceName portName instanceName
modportDecls
else ([], [origBinding])
bindingIsModport = lookupElem modports expr /= Nothing
bindingIsBundle = lookupElem modports (Dot expr "") /= Nothing
portIsBundle = null modportName
modportName = case lookup portName modportInstances of
Just (_, x) -> x
Nothing -> error $ "can't deduce modport for interface "
++ " bound to port " ++ portName
foundModport modportE =
Just (portName, (instanceE, modportE))
where instanceE = findInstance modportE
findInstance :: Expr -> Expr
findInstance e =
case lookupElem modports (Dot e "") of
Nothing -> case e of
Bit e' _ -> findInstance e'
Dot e' _ -> findInstance e'
_ -> error "internal invariant violated"
Just (accesses, _, _) ->
foldl accessToExpr (Ident topName) rest
where Access topName Nil : rest = init accesses
accessToExpr :: Expr -> Access -> Expr
accessToExpr e (Access x Nil) = Dot e x
accessToExpr e (Access x i) = Bit (Dot e x) i
-- expand a modport binding into a series of expression substitutions
expandModportBinding :: Scopes [ModportDecl]
-> ModportBinding -> [(Expr, Expr)]
expandModportBinding modports (portName, (instanceE, modportE)) =
(Ident portName, instanceE) :
map toPortBinding modportDecls
where
interfaceName = instances Map.! instanceName
interfaceItems = snd $ lookupInterface interfaceName
modportDecls = lookupModport interfaceItems modportName
expandPortBinding moduleName (origBinding @ (portName, Ident ident)) _ =
case (instances Map.!? ident, modports Map.!? ident) of
(Nothing, Nothing) -> ([], [origBinding])
(Just interfaceName, _) ->
-- given entire interface, but just bound to a modport
if Map.notMember moduleName modules then
error $ "could not find module " ++ show moduleName
else
expandPortBinding' interfaceName portName ident
modportDecls
a = lookupElem modports modportE
b = lookupElem modports (Dot modportE "")
Just (_, replacements, modportDecls) =
if a == Nothing then b else a
toPortBinding (_, x, e) = (x', e')
where
Just (_, decls) = Map.lookup moduleName modules
portType =
case lookup portName decls of
Nothing -> error $ "could not find port "
++ show portName ++ " in module "
++ show moduleName
Just t -> t
interfaceItems = snd $ lookupInterface interfaceName
modportDecls = lookupModport interfaceItems modportName
modportName = case portType of
InterfaceT _ (Just x) [] -> x
Alias _ [] -> ""
_ -> error $ "can't deduce modport for interface "
++ interfaceName ++ " bound to port "
++ portName ++ " of module " ++ moduleName
(_, Just (interfaceName, modportName)) ->
-- modport directly bound to a modport
expandPortBinding' interfaceName portName ident
(map redirect modportDecls)
where
interfaceItems = snd $ lookupInterface interfaceName
modportDecls = lookupModport interfaceItems modportName
redirect (d, x, t, _) = (d, x, t, Ident x)
expandPortBinding _ other _ = ([], [other])
expandPortBinding' :: Identifier -> Identifier -> Identifier ->
[ModportDecl] -> ([ParamBinding], [PortBinding])
expandPortBinding' interfaceName portName instanceName modportDecls =
(paramBindings, portBindings)
where
paramBindings = map toParamBinding interfaceParamNames
interfaceItems = snd $ lookupInterface interfaceName
interfaceParamNames = map fst $ parameters interfaceItems
toParamBinding x = (portName ++ '_' : x, Right $ Ident $ instanceName ++ '_' : x)
portBindings = map toPortBinding modportDecls
toPortBinding (_, x, _, e) = (x', e')
where
x' = portName ++ '_' : x
e' = traverseNestedExprs prefixExpr e
x' = Dot (Ident portName) x
e' = prefixExpr e
prefixExpr :: Expr -> Expr
prefixExpr (Ident x) = Ident (instanceName ++ '_' : x)
prefixExpr other = other
lookupInterface :: Identifier -> Interface
lookupInterface interfaceName =
case Map.lookup interfaceName interfaces of
Just res -> res
Nothing -> error $ "could not find interface " ++ show interfaceName
lookupModport :: [ModuleItem] -> Identifier -> [ModportDecl]
lookupModport interfaceItems "" = impliedModport interfaceItems
lookupModport interfaceItems modportName =
case Map.lookup modportName modportMap of
Just modportDecls -> modportDecls
Nothing -> error $ "could not find modport " ++ show modportName
where
modportMap = execWriter $
mapM (collectNestedModuleItemsM collectModport) $
interfaceItems
collectModport :: ModuleItem -> Writer (Map.Map Identifier [ModportDecl]) ()
collectModport (Modport ident l) = tell $ Map.singleton ident l
collectModport _ = return ()
impliedModport :: [ModuleItem] -> [ModportDecl]
impliedModport =
execWriter . mapM (collectNestedModuleItemsM collectModportDecls)
prefixExpr (Ident x) =
case Map.lookup x replacements of
Just replacement -> replacement
Nothing ->
if "_tmp_" `isPrefixOf` x
then Ident x
else Dot instanceE x
prefixExpr other = traverseSinglyNestedExprs prefixExpr other
-- association list of modport instances in the given module body
extractModportInstances :: PartInfo -> ModportInstances
extractModportInstances partInfo =
execWriter $ mapM (collectDeclsM collectDecl) (pItems partInfo)
where
collectModportDecls :: ModuleItem -> Writer [ModportDecl] ()
collectModportDecls (MIPackageItem (Decl (Variable d t x _ _))) =
tell [(d', x, t, Ident x)]
where d' = if d == Local then Inout else d
collectModportDecls _ = return ()
convertPort :: Identifier -> [Identifier]
convertPort ident =
case Map.lookup ident modports of
Nothing -> [ident]
Just (interfaceName, modportName) ->
map (\(_, x, _, _) -> ident ++ "_" ++ x) modportDecls
collectDecl :: Decl -> Writer ModportInstances ()
collectDecl (Variable _ t x _ _) =
if maybeInfo == Nothing then
return ()
else if elem x (pPorts partInfo) then
tell [(x, info)]
else
error $ "Modport not in port list: " ++ show (t, x)
++ ". Is this an interface missing a port list?"
where
interfaceItems = snd $ lookupInterface interfaceName
modportDecls = lookupModport interfaceItems modportName
convertDescription _ _ other = other
maybeInfo = extractModportInfo t
Just info = maybeInfo
collectDecl _ = return ()
-- replaces accesses of interface or modport members with their corresponding
-- flattened (exploded) data declarations
flattenInstances :: Instances -> Modports -> ModuleItem -> ModuleItem
flattenInstances instances modports =
\item -> evalState (rewriter item) Set.empty
extractModportInfo :: Type -> Maybe (Identifier, Identifier)
extractModportInfo (InterfaceT "" Nothing []) = Just ("", "")
extractModportInfo (InterfaceT interfaceName (Just modportName) []) =
if isInterface interfaceName
then Just (interfaceName, modportName)
else Nothing
extractModportInfo (Alias interfaceName []) =
if isInterface interfaceName
then Just (interfaceName, "")
else Nothing
extractModportInfo _ = Nothing
isInterface :: Identifier -> Bool
isInterface partName =
case Map.lookup partName parts of
Nothing -> False
Just info -> pKind info == Interface
convertDescription _ other = other
-- produce the implicit modport decls for an interface bundle
impliedModport :: [ModuleItem] -> [ModportDecl]
impliedModport =
execWriter . mapM (collectNestedModuleItemsM collectModportDecls)
where
rewriter = traverseScopesM traverseDeclM
(traverseNestedModuleItemsM traverseModuleItemM) traverseStmtM
collectModportDecls :: ModuleItem -> Writer [ModportDecl] ()
collectModportDecls (MIPackageItem (Decl (Variable d _ x _ _))) =
tell [(d', x, Ident x)]
where d' = if d == Local then Inout else d
collectModportDecls _ = return ()
-- convert an interface-bound module instantiation or an interface instantiation
-- into a series of equivalent inlined module items
inlineInstance :: [ModportBinding] -> [(Expr, Expr)] -> [ModuleItem]
-> Identifier -> [ParamBinding] -> [PortBinding] -> [ModuleItem]
inlineInstance modportBindings modportSubstitutions items
instanceName instanceParams instancePorts =
comment :
map (MIPackageItem . Decl) parameterBinds ++
Generate [GenBlock instanceName $ map GenModuleItem items']
: portBindings
where
items' = evalScoper
traverseDeclM traverseModuleItemM traverseGenItemM traverseStmtM ""
$ map (traverseNestedModuleItems rewriteItem) $
if null modportBindings
then Modport "" (impliedModport items) : items
else items
inlineKind =
if null modportBindings
then "interface"
else "interface-using module"
traverseModuleItemM :: ModuleItem -> State Idents ModuleItem
traverseModuleItemM =
traverseExprsM traverseExprM >=>
traverseLHSsM traverseLHSM
traverseStmtM :: Stmt -> State Idents Stmt
traverseStmtM =
traverseStmtExprsM traverseExprM >=>
traverseStmtLHSsM traverseLHSM
traverseDeclM :: Decl -> State Idents Decl
comment = MIPackageItem $ Decl $ CommentDecl $
"expanded " ++ inlineKind ++ " instance: " ++ instanceName
portBindings = mapMaybe portBindingItem $
filter notSubstituted instancePorts
notSubstituted :: PortBinding -> Bool
notSubstituted (portName, _) =
lookup (portName) modportBindings == Nothing
rewriteItem :: ModuleItem -> ModuleItem
rewriteItem =
removeModportInstance .
removeDeclDir .
traverseDecls overrideParam
traverseDeclM :: Decl -> Scoper Expr Decl
traverseDeclM decl = do
item <- traverseModuleItemM (MIPackageItem $ Decl decl)
let MIPackageItem (Decl decl') = item
decl' <- traverseDeclExprsM substituteExprM decl
case decl' of
Variable _ _ ident _ _ -> modify $ Set.insert ident
Param _ _ ident _ -> modify $ Set.insert ident
ParamType{} -> return ()
Variable _ _ x _ _ -> insertElem x Nil
Param _ _ x e -> insertElem x e
ParamType _ x _ -> insertElem x Nil
CommentDecl{} -> return ()
return decl'
traverseExprM = traverseNestedExprsM convertExprM
traverseLHSM = traverseNestedLHSsM convertLHSM
convertExprM :: Expr -> State Idents Expr
convertExprM (orig @ (Dot (Ident x) y)) = do
substituteNonLocal orig repl x
where repl = Ident (x ++ "_" ++ y)
convertExprM other = return other
convertLHSM :: LHS -> State Idents LHS
convertLHSM (orig @ (LHSDot (LHSIdent x) y)) = do
substituteNonLocal orig repl x
where repl = LHSIdent (x ++ "_" ++ y)
convertLHSM other = return other
substituteNonLocal :: a -> a -> Identifier -> State Idents a
substituteNonLocal orig repl ident = do
locals <- get
return $ if Map.member ident modports || Map.member ident instances
then if Set.notMember ident locals
then repl
else orig
else orig
-- add a prefix to all standard identifiers in a module item
prefixModuleItems :: (Identifier -> Identifier) -> ModuleItem -> ModuleItem
prefixModuleItems prefix =
prefixOtherItem .
traverseDecls prefixDecl .
traverseExprs (traverseNestedExprs prefixExpr) .
traverseLHSs (traverseNestedLHSs prefixLHS )
where
prefixDecl :: Decl -> Decl
prefixDecl (Variable d t x a e) = Variable d t (prefix x) a e
prefixDecl (Param s t x e) = Param s t (prefix x) e
prefixDecl (ParamType s x mt) = ParamType s (prefix x) mt
prefixDecl (CommentDecl c) = CommentDecl c
prefixExpr :: Expr -> Expr
prefixExpr (Ident x) = Ident (prefix x)
prefixExpr other = other
prefixLHS :: LHS -> LHS
prefixLHS (LHSIdent x) = LHSIdent (prefix x)
prefixLHS other = other
prefixOtherItem :: ModuleItem -> ModuleItem
prefixOtherItem (MIPackageItem item) =
MIPackageItem $ prefixPackageItem prefix item
prefixOtherItem (Instance m params name rs ports) =
Instance m params (prefix name) rs ports
prefixOtherItem (Genvar x) = Genvar $ prefix x
prefixOtherItem other = other
-- add a prefix to all standard identifiers in a package item
prefixPackageItem :: (Identifier -> Identifier) -> PackageItem -> PackageItem
prefixPackageItem prefix (Function lifetime t x decls stmts) =
Function lifetime t x' decls stmts
where x' = prefix x
prefixPackageItem prefix (Task lifetime x decls stmts) =
Task lifetime x' decls stmts
where x' = prefix x
prefixPackageItem _ other = other
-- collect all identifiers defined within a module item
collectIdentsM :: ModuleItem -> Writer (Set.Set Identifier) ()
collectIdentsM (MIPackageItem (Function _ _ x _ _)) = tell $ Set.singleton x
collectIdentsM (MIPackageItem (Task _ x _ _)) = tell $ Set.singleton x
collectIdentsM (Instance _ _ x _ _) = tell $ Set.singleton x
collectIdentsM (Genvar x) = tell $ Set.singleton x
collectIdentsM item = collectDeclsM collectDecl item
where
collectDecl :: Decl -> Writer (Set.Set Identifier) ()
collectDecl (Variable _ _ x _ _) = tell $ Set.singleton x
collectDecl (Param _ _ x _) = tell $ Set.singleton x
collectDecl (ParamType _ x _) = tell $ Set.singleton x
collectDecl (CommentDecl _) = return ()
-- convert an interface instantiation into a series of equivalent module items
inlineInterface :: Interface -> (Identifier, [ParamBinding], [PortBinding]) -> [ModuleItem]
inlineInterface (ports, items) (instanceName, instanceParams, instancePorts) =
(:) comment $
flip (++) portBindings $
map (traverseNestedModuleItems removeModport) $
map (traverseNestedModuleItems removeDeclDir) $
itemsPrefixed
where
comment = MIPackageItem $ Decl $ CommentDecl $
"expanded instance: " ++ instanceName
prefix = instanceName ++ "_"
itemsPrefixed =
map (traverseDecls overrideParam) $
prefixInterface instanceName items
origInstancePortNames = map fst instancePorts
instancePortExprs = map snd instancePorts
instancePortNames =
map (prefix ++) $
if all ("" ==) origInstancePortNames
then ports
else origInstancePortNames
portBindings =
mapMaybe portBindingItem $
zip instancePortNames instancePortExprs
traverseModuleItemM :: ModuleItem -> Scoper Expr ModuleItem
traverseModuleItemM (item @ Modport{}) =
traverseExprsM substituteExprM item
traverseModuleItemM item =
traverseExprsM traverseExprM item >>=
traverseLHSsM traverseLHSM
traverseGenItemM :: GenItem -> Scoper Expr GenItem
traverseGenItemM = traverseGenItemExprsM traverseExprM
traverseStmtM :: Stmt -> Scoper Expr Stmt
traverseStmtM =
traverseStmtExprsM traverseExprM >=>
traverseStmtLHSsM traverseLHSM
-- used for replacing usages of modports in the module being inlined
lhsReplacements = map (\(x, y) -> (toLHS x, toLHS y)) exprReplacements
exprReplacements = filter ((/= Nil) . snd) modportSubstitutions
-- LHSs are replaced using simple substitutions
traverseLHSM :: LHS -> Scoper Expr LHS
traverseLHSM lhs = do
lhs' <- embedScopes tagLHS lhs
return $ replaceLHS lhs'
tagLHS :: Scopes Expr -> LHS -> LHS
tagLHS scopes lhs =
if lookupElem scopes lhs /= Nothing
then LHSDot lhs "@"
else traverseSinglyNestedLHSs (tagLHS scopes) lhs
replaceLHS :: LHS -> LHS
replaceLHS (LHSDot lhs "@") = lhs
replaceLHS lhs =
case lookup lhs lhsReplacements of
Just lhs' -> lhs'
Nothing -> traverseSinglyNestedLHSs replaceLHS lhs
-- top-level expressions may be modports bound to other modports
traverseExprM :: Expr -> Scoper Expr Expr
traverseExprM expr = do
expr' <- embedScopes (tagExpr False) expr
return $ replaceExpr expr'
substituteExprM :: Expr -> Scoper Expr Expr
substituteExprM expr = do
expr' <- embedScopes (tagExpr True) expr
return $ replaceExpr expr'
tagExpr :: Bool -> Scopes Expr -> Expr -> Expr
tagExpr substitute scopes expr =
case lookupElem scopes expr of
Just (_, _, Nil) -> Dot expr "@"
Just ([_, _], replacements, expr') ->
if substitute && Map.null replacements
then Dot expr' "@"
else Dot expr "@"
Just (_, _, _) -> Dot expr "@"
Nothing ->
traverseSinglyNestedExprs (tagExpr substitute scopes) expr
replaceExpr :: Expr -> Expr
replaceExpr (Dot expr "@") = expr
replaceExpr (Ident x) =
case lookup x modportBindings of
Just (_, m) -> m
Nothing -> Ident x
replaceExpr expr =
replaceExpr' expr
replaceExpr' :: Expr -> Expr
replaceExpr' (Dot expr "@") = expr
replaceExpr' expr =
case lookup expr exprReplacements of
Just expr' -> expr'
Nothing -> traverseSinglyNestedExprs replaceExpr' expr
removeModportInstance :: ModuleItem -> ModuleItem
removeModportInstance (MIPackageItem (Decl (Variable d t x a e))) =
MIPackageItem $ Decl $
if lookup x modportBindings /= Nothing
then CommentDecl $ "removed modport instance " ++ x
else Variable d t x a e
removeModportInstance other = other
removeDeclDir :: ModuleItem -> ModuleItem
removeDeclDir (MIPackageItem (Decl (Variable _ t x a e))) =
......@@ -406,88 +342,80 @@ inlineInterface (ports, items) (instanceName, instanceParams, instancePorts) =
IntegerVector TLogic Unspecified rs
_ -> t
removeDeclDir other = other
removeModport :: ModuleItem -> ModuleItem
removeModport (Modport x _) =
MIPackageItem $ Decl $ CommentDecl $ "removed modport " ++ x
removeModport other = other
interfaceParamNames = map fst $ parameters items
instanceParamMap = Map.mapKeys (prefix ++) $
Map.fromList $ resolveParams interfaceParamNames instanceParams
paramTmp = "_tmp_" ++ (shortHash (items, instanceName)) ++ "_"
parameterBinds = map makeParameterBind instanceParams
makeParameterBind :: ParamBinding -> Decl
makeParameterBind (x, Left t) =
ParamType Localparam (paramTmp ++ x) (Just t)
makeParameterBind (x, Right e) =
Param Localparam (TypeOf e) (paramTmp ++ x) e
overrideParam :: Decl -> Decl
overrideParam (Param Parameter t x e) =
case Map.lookup x instanceParamMap of
Nothing -> Param Parameter t x e
Just (Right e') -> Param Parameter t x e'
Just (Left t') ->
error $ "interface param expected expression, found type: "
++ show t'
case lookup x instanceParams of
Nothing -> Param Localparam t x e
Just (Right _) -> Param Localparam t x (Ident $ paramTmp ++ x)
Just (Left t') -> error $ inlineKind ++ " param " ++ x
++ " expected expr, found type: " ++ show t'
overrideParam (ParamType Parameter x mt) =
case Map.lookup x instanceParamMap of
Nothing -> ParamType Parameter x mt
Just (Left t') -> ParamType Parameter x (Just t')
Just (Right e') ->
error $ "interface param expected type, found expression: "
++ show e'
case lookup x instanceParams of
Nothing -> ParamType Localparam x mt
Just (Left _) ->
ParamType Localparam x (Just $ Alias (paramTmp ++ x) [])
Just (Right e') -> error $ inlineKind ++ " param " ++ x
++ " expected type, found expr: " ++ show e'
overrideParam other = other
portBindingItem :: PortBinding -> Maybe ModuleItem
portBindingItem (_, Nil) = Nothing
portBindingItem (ident, expr) =
Just $ if declDirs Map.! ident == Input
then Assign AssignOptionNone (LHSIdent ident) expr
else Assign AssignOptionNone (toLHS expr) (Ident ident)
if findDeclDir ident == Input
then bind (LHSDot (LHSIdent instanceName) ident) expr
else bind (toLHS expr) (Dot (Ident instanceName) ident)
where bind a b = Just $ Assign AssignOptionNone a b
declDirs = execWriter $
mapM (collectDeclsM collectDeclDir) itemsPrefixed
mapM (collectDeclsM collectDeclDir) items
collectDeclDir :: Decl -> Writer (Map.Map Identifier Direction) ()
collectDeclDir (Variable dir _ ident _ _) =
when (dir /= Local) $
tell $ Map.singleton ident dir
collectDeclDir _ = return ()
findDeclDir :: Identifier -> Direction
findDeclDir ident =
case Map.lookup ident declDirs of
Nothing -> error $ "could not find decl dir of " ++ ident
++ " among " ++ show declDirs
Just dir -> dir
toLHS :: Expr -> LHS
toLHS expr =
case exprToLHS expr of
Just lhs -> lhs
Nothing -> error $ "trying to bind an interface output to " ++
show expr ++ " but that can't be an LHS"
-- convert an interface instantiation into a series of equivalent module items
prefixInterface :: Identifier -> [ModuleItem] -> [ModuleItem]
prefixInterface instanceName items =
map prefixItem items
where
prefix = instanceName ++ "_"
idents = execWriter $
mapM (collectNestedModuleItemsM collectIdentsM) items
prefixIfNecessary :: Identifier -> Identifier
prefixIfNecessary x =
if Set.member x idents
then prefix ++ x
else x
prefixItem = traverseNestedModuleItems $
prefixModuleItems prefixIfNecessary
-- give a set of param bindings explicit names
resolveParams :: [Identifier] -> [ParamBinding] -> [ParamBinding]
resolveParams available bindings =
map (uncurry resolveParam) $ zip bindings [0..]
Nothing -> error $ "trying to bind an " ++ inlineKind
++ " output to " ++ show expr ++ " but that can't be an LHS"
type Binding t = (Identifier, t)
-- give a set of bindings explicit names
resolveBindings :: Show t => [Identifier] -> [Binding t] -> [Binding t]
resolveBindings available bindings =
zipWith resolveBinding bindings [0..]
where
resolveParam :: ParamBinding -> Int -> ParamBinding
resolveParam ("", e) idx =
resolveBinding ("", e) idx =
if idx < length available
then (available !! idx, e)
else error $ "interface param binding " ++ (show e)
++ " is out of range"
resolveParam other _ = other
else error $ "binding " ++ show e ++ " is out of range "
++ show available
resolveBinding other _ = other
-- given a list of module items, produces the parameters in order
parameters :: [ModuleItem] -> [(Identifier, Decl)]
parameters =
-- given a list of module items, produces the parameter names in order
parameterNames :: [ModuleItem] -> [Identifier]
parameterNames =
execWriter . mapM (collectNestedModuleItemsM $ collectDeclsM collectDeclM)
where
collectDeclM :: Decl -> Writer [(Identifier, Decl)] ()
collectDeclM (decl @ (Param Parameter _ x _)) = tell [(x, decl)]
collectDeclM (decl @ (ParamType Parameter x _)) = tell [(x, decl)]
collectDeclM :: Decl -> Writer [Identifier] ()
collectDeclM (Param Parameter _ x _) = tell [x]
collectDeclM (ParamType Parameter x _) = tell [x]
collectDeclM _ = return ()
......@@ -39,6 +39,7 @@ module Convert.Scoper
, embedScopes
, withinProcedure
, withinProcedureM
, scopeModuleItemT
) where
import Control.Monad.State
......@@ -254,6 +255,20 @@ evalScoperT declMapper moduleItemMapper genItemMapper stmtMapper topName items =
return items'
initialState = Scopes [] Map.empty False []
wrappedModuleItemMapper = scopeModuleItemT
declMapper moduleItemMapper genItemMapper stmtMapper
scopeModuleItemT
:: forall a m. Monad m
=> MapperM (ScoperT a m) Decl
-> MapperM (ScoperT a m) ModuleItem
-> MapperM (ScoperT a m) GenItem
-> MapperM (ScoperT a m) Stmt
-> ModuleItem
-> ScoperT a m ModuleItem
scopeModuleItemT declMapper moduleItemMapper genItemMapper stmtMapper =
wrappedModuleItemMapper
where
fullStmtMapper :: Stmt -> ScoperT a m Stmt
fullStmtMapper (Block kw name decls stmts) = do
enterScope name ""
......
......@@ -597,10 +597,9 @@ traverseExprsM exprMapper = moduleItemMapper
genItemMapper = traverseGenItemExprsM exprMapper
modportDeclMapper (dir, ident, t, e) = do
t' <- typeMapper t
modportDeclMapper (dir, ident, e) = do
e' <- exprMapper e
return (dir, ident, t', e')
return (dir, ident, e')
traverseExprs :: Mapper Expr -> Mapper ModuleItem
traverseExprs = unmonad traverseExprsM
......@@ -942,11 +941,6 @@ traverseTypesM' strategy mapper =
then mapper t >>= \t' -> return (i, Left t')
else return (i, Left t)
mapParam (i, Right e) = return $ (i, Right e)
miMapper (Modport name decls) =
mapM mapModportDecl decls >>= return . Modport name
where
mapModportDecl (d, x, t, e) =
mapper t >>= \t' -> return (d, x, t', e)
miMapper other = return other
traverseTypes' :: TypeStrategy -> Mapper Type -> Mapper ModuleItem
......
......@@ -62,6 +62,11 @@ exprToLHS (Dot l x ) = do
exprToLHS (Concat ls ) = do
ls' <- mapM exprToLHS ls
Just $ LHSConcat ls'
exprToLHS (Pattern ls ) = do
ls' <- mapM exprToLHS $ map snd ls
if all (null . fst) ls
then Just $ LHSConcat ls'
else Nothing
exprToLHS (Stream o e ls) = do
ls' <- mapM exprToLHS ls
Just $ LHSStream o e ls'
......
......@@ -28,7 +28,7 @@ import Language.SystemVerilog.AST.Expr (Expr(Nil), pattern Ident, Range, showRan
import Language.SystemVerilog.AST.GenItem (GenItem)
import Language.SystemVerilog.AST.LHS (LHS)
import Language.SystemVerilog.AST.Stmt (Stmt, AssertionItem, Timing(Delay))
import Language.SystemVerilog.AST.Type (Type, Identifier, DriveStrength)
import Language.SystemVerilog.AST.Type (Identifier, DriveStrength)
data ModuleItem
= MIAttr Attr ModuleItem
......@@ -90,14 +90,14 @@ showGate kw d x args =
nameStr = showPad $ Ident x
showModportDecl :: ModportDecl -> String
showModportDecl (dir, ident, t, e) =
showModportDecl (dir, ident, e) =
if e == Ident ident
then printf "%s %s" (show dir) ident
else printf "%s .%s(/* type: %s */ %s)" (show dir) ident (show t) (show e)
else printf "%s .%s(%s)" (show dir) ident (show e)
type PortBinding = (Identifier, Expr)
type ModportDecl = (Direction, Identifier, Type, Expr)
type ModportDecl = (Direction, Identifier, Expr)
data AlwaysKW
= Always
......
......@@ -577,9 +577,9 @@ ParamAsgn :: { Decl }
: Identifier "=" Expr { Param Parameter (Implicit Unspecified []) $1 $3 }
PortDecls :: { ([Identifier], [ModuleItem]) }
: "(" DeclTokens(")") { parseDTsAsPortDecls $2 }
| "(" ")" { ([], []) }
| {- empty -} { ([], []) }
: "(" PortDeclTokens(")") { parseDTsAsPortDecls $2 }
| "(" ")" { ([], []) }
| {- empty -} { ([], []) }
ModportItems :: { [(Identifier, [ModportDecl])] }
: ModportItem { [$1] }
......@@ -592,7 +592,7 @@ ModportPortsDeclarations :: { [ModportDecl] }
ModportPortsDeclaration(delim) :: { [ModportDecl] }
: ModportSimplePortsDeclaration(delim) { $1 }
ModportSimplePortsDeclaration(delim) :: { [ModportDecl] }
: Direction ModportSimplePorts delim { map (\(a, b) -> ($1, a, TypeOf b, b)) $2 }
: Direction ModportSimplePorts delim { map (\(a, b) -> ($1, a, b)) $2 }
ModportSimplePorts :: { [(Identifier, Expr)] }
: ModportSimplePort { [$1] }
| ModportSimplePorts "," ModportSimplePort { $1 ++ [$3] }
......@@ -611,11 +611,13 @@ Identifiers :: { [Identifier] }
-- uses delimiter propagation hack to avoid conflicts
DeclTokens(delim) :: { [DeclToken] }
: DeclToken delim { [$1] }
| DeclToken DeclTokens(delim) { [$1] ++ $2 }
| Identifier ParamBindings DeclTokens(delim) {% posInject \p -> [DTIdent p $1, DTParams p $2] ++ $3 }
| DeclTokenAsgn "," DeclTokens(delim) {% posInject \p -> [$1, DTComma p] ++ $3 }
| DeclTokenAsgn delim {% posInject \p -> [$1] }
: DeclTokensBase(DeclTokens(delim), delim) { $1 }
DeclTokensBase(repeat, delim) :: { [DeclToken] }
: DeclToken delim { [$1] }
| DeclToken repeat { [$1] ++ $2 }
| Identifier ParamBindings repeat {% posInject \p -> [DTIdent p $1, DTParams p $2] ++ $3 }
| DeclTokenAsgn "," repeat {% posInject \p -> [$1, DTComma p] ++ $3 }
| DeclTokenAsgn delim {% posInject \p -> [$1] }
DeclToken :: { DeclToken }
: "," {% posInject \p -> DTComma p }
| "[" "]" {% posInject \p -> DTAutoDim p }
......@@ -640,6 +642,12 @@ DeclToken :: { DeclToken }
DeclTokenAsgn :: { DeclToken }
: "=" opt(DelayOrEvent) Expr {% posInject \p -> DTAsgn p AsgnOpEq $2 $3 }
| AsgnBinOp Expr {% posInject \p -> DTAsgn p $1 Nothing $2 }
PortDeclTokens(delim) :: { [DeclToken] }
: DeclTokensBase(PortDeclTokens(delim), delim) { $1 }
| GenericInterfaceDecl PortDeclTokens(delim) { $1 ++ $2}
| GenericInterfaceDecl delim { $1 }
GenericInterfaceDecl :: { [DeclToken] }
: "interface" Identifier {% posInject \p -> [DTType p (\Unspecified -> InterfaceT "" Nothing), DTIdent p $2] }
VariablePortIdentifiers :: { [(Identifier, Expr)] }
: VariablePortIdentifier { [$1] }
......
interface bundle;
logic [1:0] index;
logic clock;
logic [3:0] inp;
logic [1:0] index = 0;
logic clock = 0;
logic [3:0] inp = '1;
logic out;
endinterface
module rotator(bundle b);
initial b.index = 0;
always @(posedge b.clock)
b.index <= b.index + 1;
endmodule
module setter(bundle b);
initial b.inp = '1;
always @(posedge b.clock)
b.inp[b.index] <= b.out;
endmodule
......@@ -23,7 +21,6 @@ endmodule
module clocker(bundle b);
initial begin
b.clock <= 0;
forever
#5 b.clock <= ~b.clock;
end
......
module impl(b_index, b_clock, b_inp, b_out);
output reg [1:0] b_index;
output reg b_clock;
output reg [3:0] b_inp;
output wire b_out;
module impl;
reg [1:0] b_index;
reg b_clock;
reg [3:0] b_inp;
wire b_out;
initial b_index = 0;
always @(posedge b_clock)
......@@ -19,15 +19,6 @@ module impl(b_index, b_clock, b_inp, b_out);
forever
#5 b_clock <= ~b_clock;
end
endmodule
module top;
wire [1:0] b_index;
wire b_clock;
wire [3:0] b_inp;
wire b_out;
impl impl(b_index, b_clock, b_inp, b_out);
initial begin
$monitor("%b %b %b %b", b_index, b_clock, b_inp, b_out);
......@@ -36,3 +27,6 @@ module top;
end
endmodule
module top;
impl impl();
endmodule
interface Interface #(num_clients = 0);
bit [num_clients-1:0] req;
for (genvar i = 0; i < num_clients; ++i) begin : mps
modport client_mp (output .client_req(req[i]));
end
endinterface
module ClientAnd (client_ifc, bits);
parameter WIDTH = 2;
Interface client_ifc;
input [WIDTH-1:0] bits;
assign client_ifc.client_req = &bits;
endmodule
module ClientTick #(start = 0, period = 1) (Interface client_ifc, input clock);
initial client_ifc.client_req = start;
integer counter;
initial counter = 0;
always @(posedge clock) begin
counter += 1;
if (counter % period == 0)
client_ifc.client_req = ~client_ifc.client_req;
end
endmodule
module top;
logic clock;
initial begin
clock = 1;
forever #1 clock = ~clock;
end
parameter N = 8;
Interface #(.num_clients(N)) intf();
for (genvar j = 0; j < N - 1; j++) begin : clients
ClientTick #(j, j + 1) client(
.clock,
.client_ifc(intf.mps[j + 1].client_mp)
);
end
ClientAnd #(4) client(
.bits(intf.req[4:1]),
.client_ifc(intf.mps[0].client_mp)
);
initial begin
$monitor("%0d %b %b", $time, clock, intf.req);
#100 $finish;
end
endmodule
module ClientAnd (client_req, bits);
parameter WIDTH = 2;
output client_req;
input [WIDTH-1:0] bits;
assign client_req = &bits;
endmodule
module ClientTick #(
parameter start = 0,
parameter period = 1
) (
output reg client_req,
input clock
);
initial client_req = start;
integer counter;
initial counter = 0;
always @(posedge clock) begin
counter += 1;
if (counter % period == 0)
client_req = ~client_req;
end
endmodule
module top;
reg clock;
initial begin
clock = 1;
forever #1 clock = ~clock;
end
parameter N = 8;
generate
begin : intf
wire [N-1:0] req;
end
genvar j;
for (j = 0; j < N - 1; j = j + 1) begin : clients
ClientTick #(j, j + 1) client(
.clock,
.client_req(intf.req[j + 1])
);
end
endgenerate
ClientAnd #(4) client(
.bits(intf.req[4:1]),
.client_req(intf.req[0])
);
initial begin
$monitor("%0d %b %b", $time, clock, intf.req);
#100 $finish;
end
endmodule
interface InterfaceA;
task hello;
input integer inp;
$display("Hello from InterfaceA %0d", inp);
endtask
logic [20:0] x = 21'b01011_00100000_01011110;
endinterface
interface InterfaceB;
task hello;
input integer inp;
$display("Hello from InterfaceB %0d", inp);
endtask
logic [10:0] x = 11'b011_11110100;
endinterface
// could get bound to any of the interfaces or modports
module Module(interface i);
initial #4 i.hello(1);
initial #5 $display("Module got %b", i.x);
endmodule
interface InterfaceM;
logic [4:0] x = 0;
task hello;
input integer inp;
x = x + 1;
$display("Hello from InterfaceM %0d %b", inp, x);
endtask
modport A(input .x(x[0]));
modport B(input .x(x[2:1]));
endinterface
// could get bound to the entire interface bundle, or either modport
module ModuleM(InterfaceM i);
initial i.hello(-1);
initial $display("ModuleM got %b", i.x);
endmodule
module ModuleWrapperMA(InterfaceM.A i); Module m(i); endmodule
module ModuleWrapperMB(InterfaceM.B i); Module m(i); endmodule
module ModuleWrapperM (InterfaceM i); Module m(i); endmodule
module ModuleMWrapperMA(InterfaceM.A i); ModuleM m(i); endmodule
module ModuleMWrapperMB(InterfaceM.B i); ModuleM m(i); endmodule
module ModuleMWrapperM (InterfaceM i); ModuleM m(i); endmodule
module top;
InterfaceM im();
Module c(im.A);
Module d(im.B);
Module e(im);
ModuleM x(im.A);
ModuleM y(im.B);
ModuleM z(im);
InterfaceA ia();
InterfaceB ib();
Module a(ia);
Module b(ib);
ModuleWrapperMA cw(im);
ModuleWrapperMB dw(im);
ModuleWrapperM ew(im);
ModuleMWrapperMA xw(im);
ModuleMWrapperMB yw(im);
ModuleMWrapperM zw(im);
endmodule
module impl;
reg [4:0] im_x = 0;
task im_hello;
input integer inp;
begin
im_x = im_x + 1;
$display("Hello from InterfaceM %0d %b", inp, im_x);
end
endtask
initial #4 im_hello(1);
initial #5 $display("Module got %b", im_x[0]);
initial #4 im_hello(1);
initial #5 $display("Module got %b", im_x[2:1]);
initial #4 im_hello(1);
initial #5 $display("Module got %b", im_x);
initial im_hello(-1);
initial $display("ModuleM got %b", im_x[0]);
initial im_hello(-1);
initial $display("ModuleM got %b", im_x[2:1]);
initial im_hello(-1);
initial $display("ModuleM got %b", im_x);
task ia_hello;
input integer inp;
$display("Hello from InterfaceA %0d", inp);
endtask
wire [20:0] ia_x = 21'b01011_00100000_01011110;
task ib_hello;
input integer inp;
$display("Hello from InterfaceB %0d", inp);
endtask
wire [10:0] ib_x = 11'b011_11110100;
initial #4 ia_hello(1);
initial #5 $display("Module got %b", ia_x);
initial #4 ib_hello(1);
initial #5 $display("Module got %b", ib_x);
initial #4 im_hello(1);
initial #5 $display("Module got %b", im_x[0]);
initial #4 im_hello(1);
initial #5 $display("Module got %b", im_x[2:1]);
initial #4 im_hello(1);
initial #5 $display("Module got %b", im_x);
initial im_hello(-1);
initial $display("ModuleM got %b", im_x[0]);
initial im_hello(-1);
initial $display("ModuleM got %b", im_x[2:1]);
initial im_hello(-1);
initial $display("ModuleM got %b", im_x);
endmodule
module top;
impl impl();
endmodule
module Module(input wire x);
initial $display("Module %d", x);
endmodule
module top;
wire i_x = 0;
genvar g;
localparam SOME_VAL = 3;
initial $display("Interface %d %d", i_x, SOME_VAL);
Module m(.x(i_x));
generate
genvar g;
for (g = 10; g < 15; g = g + 1) begin
initial $display(g);
begin : i
wire x = 0;
initial $display("Interface %d %d", x, SOME_VAL);
for (g = 10; g < 15; g = g + 1) begin
initial $display(g);
end
end
for (g = 0; g < 5; g = g + 1) begin
initial $display(g);
endgenerate
generate
begin : m
initial $display("Module %d", i.x);
for (g = 0; g < 5; g = g + 1) begin
initial $display(g);
end
end
endgenerate
endmodule
......@@ -20,8 +20,8 @@ module ModuleA(Interface.ModportA m);
endmodule
module ModuleB(Interface.ModportB m);
parameter WIDTH = 0;
initial m.x = 1;
localparam WIDTH = 2 * m.WIDTH;
always @(posedge m.clock) begin
logic temp;
temp = m.x[WIDTH-1];
......@@ -33,7 +33,10 @@ module ModuleB(Interface.ModportB m);
endmodule
module ModuleBWrapper(Interface.ModportB m);
ModuleB b(m);
parameter WIDTH = 0;
ModuleB #(WIDTH) b(m);
integer i = 0;
initial #1 $display("shadow i = %d, %b", i, m.x);
endmodule
module ModuleAWrapper(Interface.ModportA m);
......@@ -45,7 +48,7 @@ module Tester(input clock);
logic [WIDTH-1:0] idx1, idx2;
Interface #(2 ** WIDTH) i(clock, '{idx1, idx2});
ModuleAWrapper a(i);
ModuleBWrapper b(i);
ModuleBWrapper #(2 * 2 ** WIDTH) b(i);
always @(negedge clock)
$display("%d %0d %2d %2d %b", $time, WIDTH, idx1, idx2, i.x);
endmodule
......@@ -10,6 +10,9 @@ module Tester(input clock);
assign idx1 = $clog2(x[2*DATA_WIDTH-1:DATA_WIDTH]);
assign idx2 = $clog2(x[DATA_WIDTH-1:0]);
integer i = 0;
initial #1 $display("shadow i = %d, %b", i, x);
always @(posedge clock) begin : block
localparam SIZE = 2 * DATA_WIDTH;
integer i;
......
interface InterfaceA;
logic x;
modport M(input x);
endinterface
interface InterfaceB;
logic y;
modport N(input y);
endinterface
module ModuleA(modport_a);
InterfaceA modport_a;
initial $display("ModuleA %b", modport_a.x);
endmodule
module ModuleB(modport_b);
InterfaceB modport_b;
InterfaceA interface_a();
ModuleA module_a(interface_a.M);
initial $display("ModuleB %b", modport_b.y);
assign interface_a.x = 0;
endmodule
module ModuleC;
InterfaceB interface_b();
ModuleB module_b(interface_b.N);
assign interface_b.y = 1;
endmodule
module top;
ModuleC module_c();
endmodule
module ModuleC;
wire y;
assign y = 1;
initial $display("ModuleB %b", y);
wire x;
assign x = 0;
initial $display("ModuleA %b", x);
endmodule
module top;
ModuleC module_c();
endmodule
module top;
wire x, f_x;
wire f_a_x, f_b_x;
assign x = 1;
assign f_x = x;
assign f_a_x = x;
assign f_b_x = ~x;
initial begin
$display("bar got %b", f_a_x);
$display("bar got %b", f_b_x);
end
wire x = 1;
generate
begin : f
wire x;
begin : a
wire x;
initial begin
$display("bar got %b", x);
end
end
assign a.x = x;
begin : b
wire x;
initial begin
$display("bar got %b", x);
end
end
assign b.x = ~x;
end
assign f.x = x;
endgenerate
endmodule
......@@ -12,10 +12,16 @@ module M(data);
endmodule
module top;
wire [31:0] x_data = 0;
wire [9:0] y_data = 0;
M #(.WIDTH(32)) a(x_data);
M #(.WIDTH(10)) b(y_data);
M #(3, 32, 4) c(x_data);
M #(5, 10, 6) d(y_data);
generate
begin : x
wire [31:0] data = 0;
end
begin : y
wire [9:0] data = 0;
end
endgenerate
M #(.WIDTH(32)) a(x.data);
M #(.WIDTH(10)) b(y.data);
M #(3, 32, 4) c(x.data);
M #(5, 10, 6) d(y.data);
endmodule
typedef struct packed { logic x; } T;
interface Interface;
integer x;
function z;
input x;
z = ~x;
endfunction
endinterface
module Module(interface y);
function z;
input T y;
z = y.x;
endfunction
integer x = 0;
initial begin
#1;
$display("x = %b", x);
$display("z(x) = %b", z(x));
$display("y.x = %b", y.x);
$display("y.z(x) = %b", y.z(x));
$display("y.z(y.x) = %b", y.z(y.x));
$display("y.z(z(y.x)) = %b", y.z(z(y.x)));
end
endmodule
module top;
Interface x();
initial x.x = 1;
Module y(x);
endmodule
module top;
generate
begin : x
integer x;
function z;
input x;
z = ~x;
endfunction
end
endgenerate
initial x.x = 1;
generate
begin : y
function z;
input x;
z = x;
endfunction
integer x = 0;
initial begin
#1;
$display("x = %b", x);
$display("z(x) = %b", z(x));
$display("y.x = %b", top.x.x);
$display("y.z(x) = %b", top.x.z(x));
$display("y.z(y.x) = %b", top.x.z(top.x.x));
$display("y.z(z(y.x)) = %b", top.x.z(z(top.x.x)));
end
end
endgenerate
endmodule
module top;
wire [3:0] i_x;
reg [1:0] i_w;
assign i_x = 4'b1001;
initial i_w = 2'b10;
generate
begin : i
wire [3:0] x;
reg [1:0] w;
end
endgenerate
assign i.x = 4'b1001;
initial i.w = 2'b10;
initial begin
$display("%b", i_x[3]);
$display("%b", i_x[2]);
$display("%b", i_x[1]);
$display("%b", i_x[0]);
$display("%b", i.x[3]);
$display("%b", i.x[2]);
$display("%b", i.x[1]);
$display("%b", i.x[0]);
end
endmodule
......@@ -25,7 +25,7 @@ module top;
clear = 1'b1;
last = 8'h0;
dataIn = 8'h0;
repeat (3) @(posedge clock);
repeat (4) @(posedge clock);
clear = 1'b0;
for (dataIn = 8'h0; dataIn <= 9'hff; dataIn = dataIn + 8'h1) begin
@(posedge clock);
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment