mirror of https://github.com/zachjs/sv2v.git
package conversion overhaul
- full import and export support - simplify AST representation of import and export - allow package-scoped identifiers invoked as subroutines - use scoped name resolution for identifiers in packages - merge package item nesting conversion into package conversion - fix handling of colliding enum items in separate modules - fix visiting enum item exprs in types
This commit is contained in:
parent
40df902887
commit
8eb3a251f7
|
|
@ -102,8 +102,9 @@ Other:
|
|||
## Supported Features
|
||||
|
||||
sv2v supports most synthesizable SystemVerilog features. Current notable
|
||||
exceptions include `export` and interface arrays. Assertions are also supported,
|
||||
but are simply dropped during conversion.
|
||||
exceptions include `defparam` on interface instances and references to typedefs
|
||||
within interface instances. Assertions are also supported, but are simply
|
||||
dropped during conversion.
|
||||
|
||||
If you find a bug or have a feature request, please create an issue. Preference
|
||||
will be given to issues which include examples or test cases.
|
||||
|
|
|
|||
|
|
@ -31,7 +31,6 @@ import qualified Convert.Logic
|
|||
import qualified Convert.LogOp
|
||||
import qualified Convert.MultiplePacked
|
||||
import qualified Convert.NamedBlock
|
||||
import qualified Convert.NestPI
|
||||
import qualified Convert.Package
|
||||
import qualified Convert.ParamNoDefault
|
||||
import qualified Convert.ParamType
|
||||
|
|
@ -86,9 +85,7 @@ phases excludes =
|
|||
, Convert.Unsigned.convert
|
||||
, Convert.SignCast.convert
|
||||
, Convert.Wildcard.convert
|
||||
, Convert.Package.convert
|
||||
, Convert.Enum.convert
|
||||
, Convert.NestPI.convert
|
||||
, Convert.ForDecl.convert
|
||||
, Convert.Jump.convert
|
||||
, Convert.Foreach.convert
|
||||
|
|
@ -111,7 +108,7 @@ run excludes = foldr (.) id $ phases excludes
|
|||
convert :: [Job.Exclude] -> Phase
|
||||
convert excludes =
|
||||
convert'
|
||||
. Convert.NestPI.reorder
|
||||
. Convert.Package.convert
|
||||
. Convert.ParamNoDefault.convert
|
||||
where
|
||||
convert' :: Phase
|
||||
|
|
|
|||
|
|
@ -3,10 +3,11 @@
|
|||
-
|
||||
- Conversion for `enum`
|
||||
-
|
||||
- This conversion replaces the enum items with localparams declared at the
|
||||
- global scope. We leave it to the package item nesting conversion to determine
|
||||
- where the generated localparams are needed. The localparams are explicitly
|
||||
- sized to match the size of the converted enum type.
|
||||
- This conversion replaces the enum items with localparams. The localparams are
|
||||
- explicitly sized to match the size of the converted enum type. For packages
|
||||
- and enums used in the global scope, these localparams are inserted in place.
|
||||
- For enums used within a module or interface, the localparams are injected as
|
||||
- needed using a nesting procedure from the package conversion.
|
||||
-
|
||||
- SystemVerilog allows for enums to have any number of the items' values
|
||||
- specified or unspecified. If the first one is unspecified, it is 0. All other
|
||||
|
|
@ -24,6 +25,7 @@ import Data.List (elemIndices)
|
|||
import qualified Data.Set as Set
|
||||
|
||||
import Convert.ExprUtils
|
||||
import Convert.Package (inject)
|
||||
import Convert.Traverse
|
||||
import Language.SystemVerilog.AST
|
||||
|
||||
|
|
@ -36,9 +38,14 @@ convert = map $ concatMap convertDescription
|
|||
convertDescription :: Description -> [Description]
|
||||
convertDescription (Package ml name items) =
|
||||
[Package ml name $ concatMap convertPackageItem items]
|
||||
convertDescription description =
|
||||
(map PackageItem enumItems) ++ [description']
|
||||
where (description', enumItems) = convertDescription' description
|
||||
convertDescription (description @ Part{}) =
|
||||
[Part attrs extern kw lifetime name ports items']
|
||||
where
|
||||
items' = inject enumItems items -- only keep what's used
|
||||
Part attrs extern kw lifetime name ports items = description'
|
||||
(description', enumItems) = convertDescription' description
|
||||
convertDescription (PackageItem item) =
|
||||
map PackageItem $ convertPackageItem item
|
||||
|
||||
-- explode a package item with its corresponding enum items
|
||||
convertPackageItem :: PackageItem -> [PackageItem]
|
||||
|
|
|
|||
|
|
@ -1,177 +0,0 @@
|
|||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-
|
||||
- Conversion for moving top-level package items into modules
|
||||
-}
|
||||
|
||||
module Convert.NestPI (convert, reorder) where
|
||||
|
||||
import Control.Monad.Writer.Strict
|
||||
import Data.Maybe (mapMaybe)
|
||||
import qualified Data.Map.Strict as Map
|
||||
import qualified Data.Set as Set
|
||||
|
||||
import Convert.Traverse
|
||||
import Language.SystemVerilog.AST
|
||||
|
||||
type PIs = Map.Map Identifier PackageItem
|
||||
type Idents = Set.Set Identifier
|
||||
|
||||
convert :: [AST] -> [AST]
|
||||
convert =
|
||||
map (filter (not . isPI)) . nest
|
||||
where
|
||||
nest :: [AST] -> [AST]
|
||||
nest = traverseFiles
|
||||
(collectDescriptionsM collectDescriptionM)
|
||||
(traverseDescriptions . convertDescription)
|
||||
isPI :: Description -> Bool
|
||||
isPI (PackageItem Import{}) = False
|
||||
isPI (PackageItem item) = piName item /= ""
|
||||
isPI _ = False
|
||||
|
||||
reorder :: [AST] -> [AST]
|
||||
reorder = map $ traverseDescriptions reorderDescription
|
||||
|
||||
-- collects packages items missing
|
||||
collectDescriptionM :: Description -> Writer PIs ()
|
||||
collectDescriptionM (PackageItem item) = do
|
||||
case piName item of
|
||||
"" -> return ()
|
||||
ident -> tell $ Map.singleton ident item
|
||||
collectDescriptionM _ = return ()
|
||||
|
||||
-- nests packages items missing from modules
|
||||
convertDescription :: PIs -> Description -> Description
|
||||
convertDescription pis (orig @ Part{}) =
|
||||
if Map.null pis
|
||||
then orig
|
||||
else Part attrs extern kw lifetime name ports items'
|
||||
where
|
||||
Part attrs extern kw lifetime name ports items = orig
|
||||
items' = addItems pis Set.empty (map addUsedPIs items)
|
||||
convertDescription _ other = other
|
||||
|
||||
-- attempt to fix simple declaration order issues
|
||||
reorderDescription :: Description -> Description
|
||||
reorderDescription (Part attrs extern kw lifetime name ports items) =
|
||||
Part attrs extern kw lifetime name ports items'
|
||||
where
|
||||
items' = addItems localPIs Set.empty (map addUsedPIs items)
|
||||
localPIs = Map.fromList $ mapMaybe toPIElem items
|
||||
toPIElem :: ModuleItem -> Maybe (Identifier, PackageItem)
|
||||
toPIElem (MIPackageItem item) = Just (piName item, item)
|
||||
toPIElem _ = Nothing
|
||||
reorderDescription other = other
|
||||
|
||||
-- iteratively inserts missing package items exactly where they are needed
|
||||
addItems :: PIs -> Idents -> [(ModuleItem, Idents)] -> [ModuleItem]
|
||||
addItems pis existingPIs ((item, usedPIs) : items) =
|
||||
if not $ Set.disjoint existingPIs thisPI then
|
||||
-- this item was re-imported earlier in the module
|
||||
addItems pis existingPIs items
|
||||
else if null itemsToAdd then
|
||||
-- this item has no additional dependencies
|
||||
item : addItems pis (Set.union existingPIs thisPI) items
|
||||
else
|
||||
-- this item has at least one un-met dependency
|
||||
addItems pis existingPIs (addUsedPIs chosen : (item, usedPIs) : items)
|
||||
where
|
||||
thisPI = execWriter $ collectPIsM item
|
||||
neededPIs = Set.difference (Set.difference usedPIs existingPIs) thisPI
|
||||
itemsToAdd = map MIPackageItem $ Map.elems $
|
||||
Map.restrictKeys pis neededPIs
|
||||
chosen = head itemsToAdd
|
||||
addItems _ _ [] = []
|
||||
|
||||
-- augment a module item with the set of identifiers it uses
|
||||
addUsedPIs :: ModuleItem -> (ModuleItem, Idents)
|
||||
addUsedPIs item =
|
||||
(item, usedPIs)
|
||||
where
|
||||
usedPIs = execWriter $
|
||||
traverseNestedModuleItemsM (traverseIdentsM writeIdent) item
|
||||
writeIdent :: Identifier -> Writer Idents Identifier
|
||||
writeIdent x = tell (Set.singleton x) >> return x
|
||||
|
||||
-- writes down the names of package items
|
||||
collectPIsM :: ModuleItem -> Writer Idents ()
|
||||
collectPIsM (MIPackageItem item) =
|
||||
case piName item of
|
||||
"" -> return ()
|
||||
ident -> tell $ Set.singleton ident
|
||||
collectPIsM _ = return ()
|
||||
|
||||
-- visits all identifiers in a module item
|
||||
traverseIdentsM :: Monad m => MapperM m Identifier -> MapperM m ModuleItem
|
||||
traverseIdentsM identMapper = traverseNodesM
|
||||
(traverseExprIdentsM identMapper)
|
||||
(traverseDeclIdentsM identMapper)
|
||||
(traverseTypeIdentsM identMapper)
|
||||
(traverseLHSIdentsM identMapper)
|
||||
(traverseStmtIdentsM identMapper)
|
||||
|
||||
-- visits all identifiers in an expression
|
||||
traverseExprIdentsM :: Monad m => MapperM m Identifier -> MapperM m Expr
|
||||
traverseExprIdentsM identMapper = fullMapper
|
||||
where
|
||||
fullMapper = exprMapper >=> traverseSinglyNestedExprsM fullMapper
|
||||
exprMapper (Call (Ident x) args) =
|
||||
identMapper x >>= \x' -> return $ Call (Ident x') args
|
||||
exprMapper (Ident x) = identMapper x >>= return . Ident
|
||||
exprMapper other = return other
|
||||
|
||||
-- visits all identifiers in a type
|
||||
traverseTypeIdentsM :: Monad m => MapperM m Identifier -> MapperM m Type
|
||||
traverseTypeIdentsM identMapper = fullMapper
|
||||
where
|
||||
fullMapper = typeMapper
|
||||
>=> traverseTypeExprsM (traverseExprIdentsM identMapper)
|
||||
>=> traverseSinglyNestedTypesM fullMapper
|
||||
typeMapper (Alias x t) = aliasHelper (Alias ) x t
|
||||
typeMapper (PSAlias p x t) = aliasHelper (PSAlias p ) x t
|
||||
typeMapper (CSAlias c p x t) = aliasHelper (CSAlias c p) x t
|
||||
typeMapper other = return other
|
||||
aliasHelper constructor x t =
|
||||
identMapper x >>= \x' -> return $ constructor x' t
|
||||
|
||||
-- visits all identifiers in an LHS
|
||||
traverseLHSIdentsM :: Monad m => MapperM m Identifier -> MapperM m LHS
|
||||
traverseLHSIdentsM identMapper = fullMapper
|
||||
where
|
||||
fullMapper = lhsMapper
|
||||
>=> traverseLHSExprsM (traverseExprIdentsM identMapper)
|
||||
>=> traverseSinglyNestedLHSsM fullMapper
|
||||
lhsMapper (LHSIdent x) = identMapper x >>= return . LHSIdent
|
||||
lhsMapper other = return other
|
||||
|
||||
-- visits all identifiers in a statement
|
||||
traverseStmtIdentsM :: Monad m => MapperM m Identifier -> MapperM m Stmt
|
||||
traverseStmtIdentsM identMapper = fullMapper
|
||||
where
|
||||
fullMapper = stmtMapper
|
||||
>=> traverseStmtExprsM (traverseExprIdentsM identMapper)
|
||||
>=> traverseStmtLHSsM (traverseLHSIdentsM identMapper)
|
||||
>=> traverseSinglyNestedStmtsM fullMapper
|
||||
stmtMapper (Subroutine (Ident x) args) =
|
||||
identMapper x >>= \x' -> return $ Subroutine (Ident x') args
|
||||
stmtMapper other = return other
|
||||
|
||||
-- visits all identifiers in a declaration
|
||||
traverseDeclIdentsM :: Monad m => MapperM m Identifier -> MapperM m Decl
|
||||
traverseDeclIdentsM identMapper =
|
||||
traverseDeclExprsM (traverseExprIdentsM identMapper) >=>
|
||||
traverseDeclTypesM (traverseTypeIdentsM identMapper)
|
||||
|
||||
-- returns the "name" of a package item, if it has one
|
||||
piName :: PackageItem -> Identifier
|
||||
piName (Function _ _ ident _ _) = ident
|
||||
piName (Task _ ident _ _) = ident
|
||||
piName (Typedef _ ident ) = ident
|
||||
piName (Decl (Variable _ _ ident _ _)) = ident
|
||||
piName (Decl (Param _ _ ident _)) = ident
|
||||
piName (Decl (ParamType _ ident _)) = ident
|
||||
piName (Decl (CommentDecl _)) = ""
|
||||
piName (Import x y) = show $ Import x y
|
||||
piName (Export _) = ""
|
||||
piName (Directive _) = ""
|
||||
|
|
@ -1,32 +1,32 @@
|
|||
{-# LANGUAGE TupleSections #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-
|
||||
- Conversion for packages, exports, and imports
|
||||
- Conversion for packages and global declarations
|
||||
-
|
||||
- TODO: We do not yet handle exports.
|
||||
- TODO: The scoping rules are not being entirely followed yet.
|
||||
- TODO: Explicit imports may introduce name conflicts because of carried items.
|
||||
- This conversion first makes a best-effort pass at resolving any simple
|
||||
- declaration ordering issues in the input. Many conversions require that
|
||||
- declarations precede their first usage.
|
||||
-
|
||||
- The SystemVerilog scoping rules for exports and imports are not entirely
|
||||
- trivial. We do not explicitly handle the "error" scenarios detailed Table
|
||||
- 26-1 of Section 26-3 of IEEE 1800-2017. Users generally shouldn't be relying
|
||||
- on this tool to catch and report such wild naming conflicts that are outlined
|
||||
- there.
|
||||
- The main phase elaborates packages and resolves imported identifiers. An
|
||||
- identifier (perhaps implicitly) referring to `P::X` is rewritten to `P_X`.
|
||||
- This conversion assumes such renaming will not cause conflicts. The full
|
||||
- semantics of imports and exports are followed.
|
||||
-
|
||||
- Summary:
|
||||
- * In scopes which have a local declaration of an identifier, that identifier
|
||||
- refers to that local declaration.
|
||||
- * If there is no local declaration, the identifier refers to the imported
|
||||
- declaration.
|
||||
- * If there is an explicit import of that identifier, the identifier refers to
|
||||
- the imported declaration.
|
||||
- * Usages of conflicting wildcard imports are not allowed.
|
||||
- Finally, because Verilog doesn't allow declarations to exist outside of
|
||||
- modules, declarations within packages and in the global scope are injected
|
||||
- into modules and interfaces as needed.
|
||||
-}
|
||||
|
||||
module Convert.Package (convert) where
|
||||
module Convert.Package
|
||||
( convert
|
||||
, inject
|
||||
) where
|
||||
|
||||
import Control.Monad.State.Strict
|
||||
import Control.Monad.Writer.Strict
|
||||
import Data.List (insert, intercalate)
|
||||
import Data.Maybe (mapMaybe)
|
||||
import qualified Data.Map.Strict as Map
|
||||
import qualified Data.Set as Set
|
||||
|
||||
|
|
@ -34,112 +34,296 @@ import Convert.Scoper
|
|||
import Convert.Traverse
|
||||
import Language.SystemVerilog.AST
|
||||
|
||||
type Packages = Map.Map Identifier PackageItems
|
||||
type PackageItems = [(Identifier, PackageItem)]
|
||||
type Packages = Map.Map Identifier Package
|
||||
type Package = (IdentStateMap, [PackageItem])
|
||||
type Idents = Set.Set Identifier
|
||||
type PIs = Map.Map Identifier PackageItem
|
||||
|
||||
convert :: [AST] -> [AST]
|
||||
convert = step
|
||||
convert files =
|
||||
map (traverseDescriptions $ convertDescription pis) files'
|
||||
where
|
||||
step :: [AST] -> [AST]
|
||||
step curr =
|
||||
if next == curr
|
||||
then curr
|
||||
else step next
|
||||
(files', packages') = convertPackages files
|
||||
pis = Map.fromList $
|
||||
concatMap (concatMap toPackageItems . snd) $
|
||||
filter (not . Map.null . fst) $
|
||||
Map.elems packages'
|
||||
toPackageItems :: PackageItem -> [(Identifier, PackageItem)]
|
||||
toPackageItems item = map (, item) (piNames item)
|
||||
|
||||
-- utility for inserting package items into a set of module items as needed
|
||||
inject :: [PackageItem] -> [ModuleItem] -> [ModuleItem]
|
||||
inject packageItems items =
|
||||
addItems localPIs Set.empty (map addUsedPIs items)
|
||||
where
|
||||
localPIs = Map.fromList $ concatMap toPIElem packageItems
|
||||
toPIElem :: PackageItem -> [(Identifier, PackageItem)]
|
||||
toPIElem item = map (, item) (piNames item)
|
||||
|
||||
-- collect packages and global package items
|
||||
collectPackageM :: Description -> Writer (Packages, [PackageItem]) ()
|
||||
collectPackageM (PackageItem item) =
|
||||
when (not $ null $ piNames item) $
|
||||
tell (Map.empty, [item])
|
||||
collectPackageM (Package _ name items) =
|
||||
tell (Map.singleton name (Map.empty, items), [])
|
||||
collectPackageM _ = return ()
|
||||
|
||||
-- elaborate all packages and their usages
|
||||
convertPackages :: [AST] -> ([AST], Packages)
|
||||
convertPackages files =
|
||||
(files', packages')
|
||||
where
|
||||
(files', ([], packages')) = runState op ([], packages)
|
||||
op = mapM (traverseDescriptionsM traverseDescriptionM) files
|
||||
packages = Map.insert "" (Map.empty, globalItems) realPackages
|
||||
(realPackages, globalItems) =
|
||||
execWriter $ mapM (collectDescriptionsM collectPackageM) files
|
||||
|
||||
type PackagesState = State ([Identifier], Packages)
|
||||
|
||||
traverseDescriptionM :: Description -> PackagesState Description
|
||||
traverseDescriptionM (PackageItem item) = do
|
||||
return $ PackageItem $ case piNames item of
|
||||
[] -> item
|
||||
idents -> Decl $ CommentDecl $ "removed " ++ show idents
|
||||
traverseDescriptionM (Package _ name _) =
|
||||
return $ PackageItem $ Decl $ CommentDecl $ "removed package " ++ show name
|
||||
traverseDescriptionM (Part attrs extern kw liftetime name ports items) = do
|
||||
(_, items') <- processItems name "" items
|
||||
return $ Part attrs extern kw liftetime name ports items'
|
||||
|
||||
data IdentState
|
||||
= Available [Identifier]
|
||||
| Imported Identifier
|
||||
| Declared
|
||||
deriving Eq
|
||||
|
||||
isImported :: IdentState -> Bool
|
||||
isImported Imported{} = True
|
||||
isImported _ = False
|
||||
|
||||
isDeclared :: IdentState -> Bool
|
||||
isDeclared Declared{} = True
|
||||
isDeclared _ = False
|
||||
|
||||
type IdentStateMap = Map.Map Identifier IdentState
|
||||
type Scope = ScoperT IdentState PackagesState
|
||||
|
||||
-- produce the partial mapping for a particular export and ensure its validity
|
||||
resolveExport
|
||||
:: IdentStateMap -> Identifier -> Identifier -> PackagesState IdentStateMap
|
||||
resolveExport mapping "" "" =
|
||||
return $ Map.filter isImported mapping
|
||||
resolveExport mapping pkg "" =
|
||||
fmap (Map.mapMaybeWithKey checkExport . fst) (findPackage pkg)
|
||||
where
|
||||
checkExport :: Identifier -> IdentState -> Maybe IdentState
|
||||
checkExport ident exportedIdentState =
|
||||
if localIdentState == expectedIdentState
|
||||
then localIdentState
|
||||
else Nothing
|
||||
where
|
||||
next = traverseFiles
|
||||
(collectDescriptionsM collectDescriptionM)
|
||||
convertFile curr
|
||||
localIdentState = Map.lookup ident mapping
|
||||
expectedIdentState = Just $ Imported $
|
||||
toRootPackage pkg exportedIdentState
|
||||
resolveExport mapping pkg ident =
|
||||
case Map.lookup ident mapping of
|
||||
Just (Imported importedPkg) -> do
|
||||
exportedPkg <- resolveRootPackage pkg ident
|
||||
if importedPkg == exportedPkg
|
||||
then return $ Map.singleton ident $ Imported importedPkg
|
||||
else error $ "export of " ++ pkg ++ "::" ++ ident
|
||||
++ " differs from import of " ++ importedPkg
|
||||
++ "::" ++ ident
|
||||
_ -> error $ "export of " ++ pkg ++ "::" ++ ident
|
||||
++ ", but " ++ ident ++ " was never imported"
|
||||
|
||||
convertFile :: Packages -> AST -> AST
|
||||
convertFile packages ast =
|
||||
(++) globalItems $
|
||||
filter (not . isCollected) $
|
||||
concatMap (traverseDescription packages) $
|
||||
ast
|
||||
-- lookup the state of the identifier only within the current scope
|
||||
lookupLocalIdentState :: Identifier -> Scope (Maybe IdentState)
|
||||
lookupLocalIdentState =
|
||||
fmap (fmap thd3) . lookupLocalIdentM
|
||||
where thd3 (_, _, c) = c
|
||||
|
||||
-- make a particular identifier within a package available for import
|
||||
wildcardImport :: Identifier -> Identifier -> Scope ()
|
||||
wildcardImport pkg ident = do
|
||||
rootPkg <- lift $ resolveRootPackage pkg ident
|
||||
maybeIdentState <- lookupLocalIdentState ident
|
||||
insertElem ident $
|
||||
case maybeIdentState of
|
||||
Nothing -> Available [rootPkg]
|
||||
Just Declared -> Declared
|
||||
Just (Imported existingRootPkg) -> Imported existingRootPkg
|
||||
Just (Available rootPkgs) ->
|
||||
if elem rootPkg rootPkgs
|
||||
then Available rootPkgs
|
||||
else Available $ insert rootPkg rootPkgs
|
||||
|
||||
-- make all exported identifiers within a package available for import
|
||||
wildcardImports :: Identifier -> Scope ()
|
||||
wildcardImports pkg = do
|
||||
(exports, _) <- lift $ findPackage pkg
|
||||
_ <- mapM (wildcardImport pkg) (Map.keys exports)
|
||||
return ()
|
||||
|
||||
-- resolve and store an explicit (non-wildcard) import
|
||||
explicitImport :: Identifier -> Identifier -> Scope ()
|
||||
explicitImport pkg ident = do
|
||||
rootPkg <- lift $ resolveRootPackage pkg ident
|
||||
maybeIdentState <- lookupLocalIdentState ident
|
||||
insertElem ident $
|
||||
case maybeIdentState of
|
||||
Nothing -> Imported rootPkg
|
||||
Just Declared ->
|
||||
error $ "import of " ++ pkg ++ "::" ++ ident
|
||||
++ " conflicts with prior declaration of " ++ ident
|
||||
Just Available{} -> Imported rootPkg
|
||||
Just (Imported otherPkg) ->
|
||||
if otherPkg == rootPkg
|
||||
then Imported rootPkg
|
||||
else error $ "import of " ++ pkg ++ "::" ++ ident
|
||||
++ " conflicts with prior import of "
|
||||
++ otherPkg ++ "::" ++ ident
|
||||
|
||||
-- main logic responsible for translating packages, resolving imports and
|
||||
-- exports, and rewriting identifiers referring to package declarations
|
||||
processItems :: Identifier -> Identifier -> [ModuleItem]
|
||||
-> PackagesState (IdentStateMap, [ModuleItem])
|
||||
processItems topName packageName moduleItems = do
|
||||
(moduleItems', scopes) <- runScoperT
|
||||
traverseDeclM traverseModuleItemM traverseGenItemM traverseStmtM
|
||||
topName (reorderItems moduleItems)
|
||||
let rawIdents = extractMapping scopes
|
||||
externalIdentMaps <- mapM (resolveExportMI rawIdents) moduleItems
|
||||
let externalIdents = Map.unions externalIdentMaps
|
||||
let declaredIdents = Map.filter isDeclared rawIdents
|
||||
let exports = Map.union declaredIdents externalIdents
|
||||
let exports' = if null packageName
|
||||
then rawIdents
|
||||
else exports
|
||||
seq exports return (exports', moduleItems')
|
||||
where
|
||||
globalItems = map PackageItem $
|
||||
concatMap (uncurry globalPackageItems) $ Map.toList packages
|
||||
isCollected :: Description -> Bool
|
||||
isCollected (Package _ name _) = Map.member name packages
|
||||
isCollected _ = False
|
||||
-- produces partial mappings of exported identifiers, while also
|
||||
-- checking the validity of the exports
|
||||
resolveExportMI :: IdentStateMap -> ModuleItem -> PackagesState IdentStateMap
|
||||
resolveExportMI mapping (MIPackageItem (item @ (Export pkg ident))) =
|
||||
if null packageName
|
||||
then error $ "invalid " ++ (init $ show item)
|
||||
++ " outside of package"
|
||||
else resolveExport mapping pkg ident
|
||||
resolveExportMI _ _ = return Map.empty
|
||||
|
||||
globalPackageItems :: Identifier -> PackageItems -> [PackageItem]
|
||||
globalPackageItems name items =
|
||||
prefixPackageItems name (packageItemIdents items) (map snd items)
|
||||
-- declare an identifier, prefixing it if within a package
|
||||
prefixIdent :: Identifier -> Scope Identifier
|
||||
prefixIdent x = do
|
||||
inProcedure <- withinProcedureM
|
||||
maybeIdentState <- lookupLocalIdentState x
|
||||
case maybeIdentState of
|
||||
Just (Imported rootPkg) -> error $ "declaration of " ++ x
|
||||
++ " conflicts with prior import of " ++ rootPkg
|
||||
++ "::" ++ x
|
||||
_ -> do
|
||||
insertElem x Declared
|
||||
if inProcedure || null packageName
|
||||
then return x
|
||||
else return $ packageName ++ '_' : x
|
||||
|
||||
packageItemIdents :: PackageItems -> Idents
|
||||
packageItemIdents items =
|
||||
Set.union
|
||||
(Set.fromList $ map fst items)
|
||||
(Set.unions $ map (packageItemSubIdents . snd) items)
|
||||
where
|
||||
packageItemSubIdents :: PackageItem -> Idents
|
||||
packageItemSubIdents (Typedef (Enum _ enumItems _) _) =
|
||||
Set.fromList $ map fst enumItems
|
||||
packageItemSubIdents _ = Set.empty
|
||||
-- check the global scope for declarations or imports
|
||||
resolveGlobalIdent :: Identifier -> Scope Identifier
|
||||
resolveGlobalIdent x = do
|
||||
(exports, _) <- lift $ findPackage ""
|
||||
case Map.lookup x exports of
|
||||
Nothing -> return x
|
||||
Just identState -> do
|
||||
-- inject the exact state outside of the module scope,
|
||||
-- allowing wildcard imports to be handled correctly
|
||||
insertElem [Access x Nil] identState
|
||||
resolveIdent x
|
||||
|
||||
prefixPackageItems :: Identifier -> Idents -> [PackageItem] -> [PackageItem]
|
||||
prefixPackageItems packageName idents items =
|
||||
map unwrap $ evalScoper
|
||||
traverseDeclM traverseModuleItemM traverseGenItemM traverseStmtM
|
||||
packageName $ map (wrap . initialPrefix) items
|
||||
where
|
||||
wrap :: PackageItem -> ModuleItem
|
||||
wrap = MIPackageItem
|
||||
unwrap :: ModuleItem -> PackageItem
|
||||
unwrap (MIPackageItem item) = item
|
||||
unwrap _ = error "unwrap invariant violated"
|
||||
|
||||
initialPrefix :: PackageItem -> PackageItem
|
||||
initialPrefix item =
|
||||
case item of
|
||||
Function a b x c d -> Function a b (prefix x) c d
|
||||
Task a x c d -> Task a (prefix x) c d
|
||||
Typedef a x -> Typedef a (prefix x)
|
||||
Decl (Variable a b x c d) -> Decl (Variable a b (prefix x) c d)
|
||||
Decl (Param a b x c ) -> Decl (Param a b (prefix x) c )
|
||||
Decl (ParamType a x b ) -> Decl (ParamType a (prefix x) b )
|
||||
other -> other
|
||||
|
||||
prefix :: Identifier -> Identifier
|
||||
prefix x =
|
||||
if Set.member x idents
|
||||
then packageName ++ '_' : x
|
||||
else x
|
||||
prefixM :: Identifier -> Scoper () Identifier
|
||||
prefixM x = do
|
||||
-- remap an identifier if needed based on declarations, explicit
|
||||
-- imports, or names available for import
|
||||
resolveIdent :: Identifier -> Scope Identifier
|
||||
resolveIdent x = do
|
||||
details <- lookupElemM x
|
||||
if details == Nothing
|
||||
then return $ prefix x
|
||||
else return x
|
||||
case details of
|
||||
Nothing ->
|
||||
if null topName
|
||||
then return x
|
||||
else resolveGlobalIdent x
|
||||
Just ([_, _], _, Declared) ->
|
||||
if null packageName
|
||||
then return x
|
||||
else return $ packageName ++ '_' : x
|
||||
Just (_, _, Declared) -> return x
|
||||
Just (_, _, Imported rootPkg) ->
|
||||
return $ rootPkg ++ '_' : x
|
||||
Just (accesses, _, Available [rootPkg]) -> do
|
||||
insertElem accesses $ Imported rootPkg
|
||||
return $ rootPkg ++ '_' : x
|
||||
Just (_, _, Available rootPkgs) ->
|
||||
error $ "identifier " ++ show x
|
||||
++ " ambiguously refers to the definitions in any of "
|
||||
++ intercalate ", " rootPkgs
|
||||
|
||||
traverseDeclM :: Decl -> Scoper () Decl
|
||||
traversePackageItemM :: PackageItem -> Scope PackageItem
|
||||
-- TODO: fold this in with type parameters
|
||||
traversePackageItemM (Typedef t x) = do
|
||||
t' <- traverseTypeM t
|
||||
x' <- prefixIdent x
|
||||
t'' <- traverseNestedTypesM (traverseTypeExprsM traverseExprM) t'
|
||||
return $ Typedef t'' x'
|
||||
traversePackageItemM (orig @ (Import pkg ident)) = do
|
||||
if null ident
|
||||
then wildcardImports pkg
|
||||
else explicitImport pkg ident
|
||||
return $ Decl $ CommentDecl $ "removed " ++ show orig
|
||||
traversePackageItemM (orig @ (Export pkg ident)) = do
|
||||
() <- when (not (null pkg || null ident)) $ do
|
||||
localName <- resolveIdent ident
|
||||
rootPkg <- lift $ resolveRootPackage pkg ident
|
||||
localName `seq` rootPkg `seq` return ()
|
||||
return $ Decl $ CommentDecl $ "removed " ++ show orig
|
||||
traversePackageItemM other = return other
|
||||
|
||||
traverseDeclM :: Decl -> Scope Decl
|
||||
traverseDeclM decl = do
|
||||
case decl of
|
||||
Variable _ _ x _ _ -> insertElem x ()
|
||||
Param _ _ x _ -> insertElem x ()
|
||||
ParamType _ x _ -> insertElem x ()
|
||||
CommentDecl{} -> return ()
|
||||
traverseDeclTypesM traverseTypeM decl >>=
|
||||
decl' <- case decl of
|
||||
Variable d t x a e -> declHelp x $ \x' -> Variable d t x' a e
|
||||
Param p t x e -> declHelp x $ \x' -> Param p t x' e
|
||||
ParamType p x t -> declHelp x $ \x' -> ParamType p x' t
|
||||
CommentDecl c -> return $ CommentDecl c
|
||||
traverseDeclTypesM traverseTypeM decl' >>=
|
||||
traverseDeclExprsM traverseExprM
|
||||
where declHelp x f = prefixIdent x >>= return . f
|
||||
|
||||
traverseTypeM :: Type -> Scoper () Type
|
||||
traverseTypeM :: Type -> Scope Type
|
||||
traverseTypeM (PSAlias p x rs) = do
|
||||
x' <- lift $ resolvePSIdent p x
|
||||
return $ Alias x' rs
|
||||
traverseTypeM (Alias x rs) =
|
||||
prefixM x >>= \x' -> return $ Alias x' rs
|
||||
resolveIdent x >>= \x' -> return $ Alias x' rs
|
||||
traverseTypeM (Enum t enumItems rs) = do
|
||||
enumItems' <- mapM prefixEnumItem enumItems
|
||||
return $ Enum t enumItems' rs
|
||||
where prefixEnumItem (x, e) = prefixM x >>= \x' -> return (x', e)
|
||||
where prefixEnumItem (x, e) = prefixIdent x >>= \x' -> return (x', e)
|
||||
traverseTypeM other = traverseSinglyNestedTypesM traverseTypeM other
|
||||
|
||||
traverseExprM (Ident x) = prefixM x >>= return . Ident
|
||||
traverseExprM (PSIdent p x) = do
|
||||
x' <- lift $ resolvePSIdent p x
|
||||
return $ Ident x'
|
||||
traverseExprM (Ident x) = resolveIdent x >>= return . Ident
|
||||
traverseExprM other = traverseSinglyNestedExprsM traverseExprM other
|
||||
traverseLHSM (LHSIdent x) = prefixM x >>= return . LHSIdent
|
||||
traverseLHSM (LHSIdent x) = resolveIdent x >>= return . LHSIdent
|
||||
traverseLHSM other = traverseSinglyNestedLHSsM traverseLHSM other
|
||||
|
||||
traverseGenItemM = error "not possible"
|
||||
traverseModuleItemM =
|
||||
traverseGenItemM = traverseGenItemExprsM traverseExprM
|
||||
traverseModuleItemM (MIPackageItem item) = do
|
||||
item' <- traversePackageItemM item
|
||||
return $ MIPackageItem item'
|
||||
traverseModuleItemM other =
|
||||
traverseModuleItemM' other
|
||||
traverseModuleItemM' =
|
||||
traverseTypesM traverseTypeM >=>
|
||||
traverseExprsM traverseExprM >=>
|
||||
traverseLHSsM traverseLHSM
|
||||
|
|
@ -147,84 +331,200 @@ prefixPackageItems packageName idents items =
|
|||
traverseStmtExprsM traverseExprM >=>
|
||||
traverseStmtLHSsM traverseLHSM
|
||||
|
||||
collectDescriptionM :: Description -> Writer Packages ()
|
||||
collectDescriptionM (Package _ name items) =
|
||||
if any isImport items
|
||||
then return ()
|
||||
else tell $ Map.singleton name itemList
|
||||
where
|
||||
itemList = concatMap toPackageItems items
|
||||
toPackageItems :: PackageItem -> PackageItems
|
||||
toPackageItems item =
|
||||
case piName item of
|
||||
"" -> []
|
||||
x -> [(x, item)]
|
||||
isImport :: PackageItem -> Bool
|
||||
isImport (Import _ _) = True
|
||||
isImport _ = False
|
||||
collectDescriptionM _ = return ()
|
||||
-- locate a package by name, processing its contents if necessary
|
||||
findPackage :: Identifier -> PackagesState Package
|
||||
findPackage packageName = do
|
||||
(stack, packages) <- get
|
||||
let maybePackage = Map.lookup packageName packages
|
||||
assertMsg (maybePackage /= Nothing) $
|
||||
"could not find package " ++ show packageName
|
||||
-- because this conversion doesn't enforce declaration ordering of packages,
|
||||
-- it must check for dependency loops to avoid infinite recursion
|
||||
let first : rest = reverse $ packageName : stack
|
||||
assertMsg (not $ elem packageName stack) $
|
||||
"package dependency loop: " ++ show first ++ " depends on "
|
||||
++ intercalate ", which depends on " (map show rest)
|
||||
let Just (package @ (exports, _))= maybePackage
|
||||
if Map.null exports
|
||||
then do
|
||||
-- process and resolve this package
|
||||
put (packageName : stack, packages)
|
||||
package' <- processPackage packageName $ snd package
|
||||
packages' <- gets snd
|
||||
put (stack, Map.insert packageName package' packages')
|
||||
return package'
|
||||
else return package
|
||||
|
||||
traverseDescription :: Packages -> Description -> [Description]
|
||||
traverseDescription packages (PackageItem (Import x y)) =
|
||||
map (\(MIPackageItem item) -> PackageItem item) items
|
||||
-- helper for elaborating a package when it is first referenced
|
||||
processPackage :: Identifier -> [PackageItem] -> PackagesState Package
|
||||
processPackage packageName packageItems = do
|
||||
(exports, moduleItems') <- processItems packageName packageName wrapped
|
||||
let packageItems' = map unwrap moduleItems'
|
||||
let package' = (exports, packageItems')
|
||||
return package'
|
||||
where
|
||||
orig = Part [] False Module Inherit "DNE" []
|
||||
[MIPackageItem $ Import x y]
|
||||
[orig'] = traverseDescription packages orig
|
||||
Part [] False Module Inherit "DNE" [] items = orig'
|
||||
traverseDescription packages description =
|
||||
[description']
|
||||
wrapped = map wrap packageItems
|
||||
wrap :: PackageItem -> ModuleItem
|
||||
wrap = MIPackageItem
|
||||
unwrap :: ModuleItem -> PackageItem
|
||||
unwrap packageItem = item
|
||||
where MIPackageItem item = packageItem
|
||||
|
||||
-- resolve a package scoped identifier to its unique global name
|
||||
resolvePSIdent :: Identifier -> Identifier -> PackagesState Identifier
|
||||
resolvePSIdent packageName itemName = do
|
||||
rootPkg <- resolveRootPackage packageName itemName
|
||||
return $ rootPkg ++ '_' : itemName
|
||||
|
||||
-- determines the root package contained the given package scoped identifier
|
||||
resolveRootPackage :: Identifier -> Identifier -> PackagesState Identifier
|
||||
resolveRootPackage packageName itemName = do
|
||||
(exports, _) <- findPackage packageName
|
||||
let maybeIdentState = Map.lookup itemName exports
|
||||
assertMsg (maybeIdentState /= Nothing) $
|
||||
"could not find " ++ show itemName ++ " in package " ++ show packageName
|
||||
let Just identState = maybeIdentState
|
||||
return $ toRootPackage packageName identState
|
||||
|
||||
-- errors with the given message when the check is false
|
||||
assertMsg :: Monad m => Bool -> String -> m ()
|
||||
assertMsg check msg = when (not check) $ error msg
|
||||
|
||||
-- helper for taking an ident which is either declared or exported form a
|
||||
-- package and determine its true root source package
|
||||
toRootPackage :: Identifier -> IdentState -> Identifier
|
||||
toRootPackage sourcePackage identState =
|
||||
if identState == Declared
|
||||
then sourcePackage
|
||||
else rootPackage
|
||||
where Imported rootPackage = identState
|
||||
|
||||
-- nests packages items missing from modules
|
||||
convertDescription :: PIs -> Description -> Description
|
||||
convertDescription pis (orig @ Part{}) =
|
||||
if Map.null pis
|
||||
then orig
|
||||
else Part attrs extern kw lifetime name ports items'
|
||||
where
|
||||
description' = traverseModuleItems
|
||||
(traverseModuleItem existingItemNames packages)
|
||||
description
|
||||
existingItemNames = execWriter $
|
||||
collectModuleItemsM writePIName description
|
||||
writePIName :: ModuleItem -> Writer Idents ()
|
||||
writePIName (MIPackageItem (Import _ (Just x))) =
|
||||
tell $ Set.singleton x
|
||||
writePIName (MIPackageItem item) =
|
||||
case piName item of
|
||||
"" -> return ()
|
||||
x -> tell $ Set.singleton x
|
||||
writePIName _ = return ()
|
||||
Part attrs extern kw lifetime name ports items = orig
|
||||
items' = addItems pis Set.empty (map addUsedPIs items)
|
||||
convertDescription _ other = other
|
||||
|
||||
traverseModuleItem :: Idents -> Packages -> ModuleItem -> ModuleItem
|
||||
traverseModuleItem existingItemNames packages (MIPackageItem (Import x y)) =
|
||||
if Map.member x packages
|
||||
then Generate $ map (GenModuleItem . MIPackageItem) itemsRenamed
|
||||
else MIPackageItem $ Import x y
|
||||
-- attempt to fix simple declaration order issues
|
||||
reorderItems :: [ModuleItem] -> [ModuleItem]
|
||||
reorderItems items =
|
||||
addItems localPIs Set.empty (map addUsedPIs items)
|
||||
where
|
||||
packageItems = packages Map.! x
|
||||
namesToAvoid = case y of
|
||||
Nothing -> existingItemNames
|
||||
Just ident -> Set.delete ident existingItemNames
|
||||
itemsRenamed =
|
||||
prefixPackageItems x namesToAvoid
|
||||
(map snd packageItems)
|
||||
traverseModuleItem _ _ item =
|
||||
(traverseExprs $ traverseNestedExprs traverseExpr) $
|
||||
(traverseTypes $ traverseNestedTypes traverseType) $
|
||||
item
|
||||
localPIs = Map.fromList $ concat $ mapMaybe toPIElem items
|
||||
toPIElem :: ModuleItem -> Maybe [(Identifier, PackageItem)]
|
||||
toPIElem (MIPackageItem item) = Just $ map (, item) (piNames item)
|
||||
toPIElem _ = Nothing
|
||||
|
||||
-- iteratively inserts missing package items exactly where they are needed
|
||||
addItems :: PIs -> Idents -> [(ModuleItem, Idents)] -> [ModuleItem]
|
||||
addItems pis existingPIs ((item, usedPIs) : items) =
|
||||
if not $ Set.disjoint existingPIs thisPI then
|
||||
-- this item was re-imported earlier in the module
|
||||
addItems pis existingPIs items
|
||||
else if null itemsToAdd then
|
||||
-- this item has no additional dependencies
|
||||
item : addItems pis (Set.union existingPIs thisPI) items
|
||||
else
|
||||
-- this item has at least one un-met dependency
|
||||
addItems pis existingPIs (addUsedPIs chosen : (item, usedPIs) : items)
|
||||
where
|
||||
thisPI = case item of
|
||||
MIPackageItem packageItem ->
|
||||
Set.fromList $ piNames packageItem
|
||||
_ -> Set.empty
|
||||
neededPIs = Set.difference (Set.difference usedPIs existingPIs) thisPI
|
||||
itemsToAdd = map MIPackageItem $ Map.elems $
|
||||
Map.restrictKeys pis neededPIs
|
||||
chosen = head itemsToAdd
|
||||
addItems _ _ [] = []
|
||||
|
||||
traverseExpr :: Expr -> Expr
|
||||
traverseExpr (PSIdent x y) = Ident $ x ++ "_" ++ y
|
||||
traverseExpr other = other
|
||||
-- augment a module item with the set of identifiers it uses
|
||||
addUsedPIs :: ModuleItem -> (ModuleItem, Idents)
|
||||
addUsedPIs item =
|
||||
(item, usedPIs)
|
||||
where
|
||||
usedPIs = execWriter $
|
||||
traverseNestedModuleItemsM (traverseIdentsM writeIdent) item
|
||||
writeIdent :: Identifier -> Writer Idents Identifier
|
||||
writeIdent x = tell (Set.singleton x) >> return x
|
||||
|
||||
traverseType :: Type -> Type
|
||||
traverseType (PSAlias ps xx rs) = Alias (ps ++ "_" ++ xx) rs
|
||||
traverseType other = other
|
||||
-- visits all identifiers in a module item
|
||||
traverseIdentsM :: Monad m => MapperM m Identifier -> MapperM m ModuleItem
|
||||
traverseIdentsM identMapper = traverseNodesM
|
||||
(traverseExprIdentsM identMapper)
|
||||
(traverseDeclIdentsM identMapper)
|
||||
(traverseTypeIdentsM identMapper)
|
||||
(traverseLHSIdentsM identMapper)
|
||||
(traverseStmtIdentsM identMapper)
|
||||
|
||||
-- returns the "name" of a package item, if it has one
|
||||
piName :: PackageItem -> Identifier
|
||||
piName (Function _ _ ident _ _) = ident
|
||||
piName (Task _ ident _ _) = ident
|
||||
piName (Typedef _ ident ) = ident
|
||||
piName (Decl (Variable _ _ ident _ _)) = ident
|
||||
piName (Decl (Param _ _ ident _)) = ident
|
||||
piName (Decl (ParamType _ ident _)) = ident
|
||||
piName (Decl (CommentDecl _)) = ""
|
||||
piName (Import _ _) = ""
|
||||
piName (Export _) = ""
|
||||
piName (Directive _) = ""
|
||||
-- visits all identifiers in an expression
|
||||
traverseExprIdentsM :: Monad m => MapperM m Identifier -> MapperM m Expr
|
||||
traverseExprIdentsM identMapper = fullMapper
|
||||
where
|
||||
fullMapper = exprMapper >=> traverseSinglyNestedExprsM fullMapper
|
||||
exprMapper (Call (Ident x) args) =
|
||||
identMapper x >>= \x' -> return $ Call (Ident x') args
|
||||
exprMapper (Ident x) = identMapper x >>= return . Ident
|
||||
exprMapper other = return other
|
||||
|
||||
-- visits all identifiers in a type
|
||||
traverseTypeIdentsM :: Monad m => MapperM m Identifier -> MapperM m Type
|
||||
traverseTypeIdentsM identMapper = fullMapper
|
||||
where
|
||||
fullMapper = typeMapper
|
||||
>=> traverseTypeExprsM (traverseExprIdentsM identMapper)
|
||||
>=> traverseSinglyNestedTypesM fullMapper
|
||||
typeMapper (Alias x t) = aliasHelper (Alias ) x t
|
||||
typeMapper (PSAlias p x t) = aliasHelper (PSAlias p ) x t
|
||||
typeMapper (CSAlias c p x t) = aliasHelper (CSAlias c p) x t
|
||||
typeMapper other = return other
|
||||
aliasHelper constructor x t =
|
||||
identMapper x >>= \x' -> return $ constructor x' t
|
||||
|
||||
-- visits all identifiers in an LHS
|
||||
traverseLHSIdentsM :: Monad m => MapperM m Identifier -> MapperM m LHS
|
||||
traverseLHSIdentsM identMapper = fullMapper
|
||||
where
|
||||
fullMapper = lhsMapper
|
||||
>=> traverseLHSExprsM (traverseExprIdentsM identMapper)
|
||||
>=> traverseSinglyNestedLHSsM fullMapper
|
||||
lhsMapper (LHSIdent x) = identMapper x >>= return . LHSIdent
|
||||
lhsMapper other = return other
|
||||
|
||||
-- visits all identifiers in a statement
|
||||
traverseStmtIdentsM :: Monad m => MapperM m Identifier -> MapperM m Stmt
|
||||
traverseStmtIdentsM identMapper = fullMapper
|
||||
where
|
||||
fullMapper = stmtMapper
|
||||
>=> traverseStmtExprsM (traverseExprIdentsM identMapper)
|
||||
>=> traverseStmtLHSsM (traverseLHSIdentsM identMapper)
|
||||
>=> traverseSinglyNestedStmtsM fullMapper
|
||||
stmtMapper (Subroutine (Ident x) args) =
|
||||
identMapper x >>= \x' -> return $ Subroutine (Ident x') args
|
||||
stmtMapper other = return other
|
||||
|
||||
-- visits all identifiers in a declaration
|
||||
traverseDeclIdentsM :: Monad m => MapperM m Identifier -> MapperM m Decl
|
||||
traverseDeclIdentsM identMapper =
|
||||
traverseDeclExprsM (traverseExprIdentsM identMapper) >=>
|
||||
traverseDeclTypesM (traverseTypeIdentsM identMapper)
|
||||
|
||||
-- returns any names defined by a package item
|
||||
piNames :: PackageItem -> [Identifier]
|
||||
piNames (Function _ _ ident _ _) = [ident]
|
||||
piNames (Task _ ident _ _) = [ident]
|
||||
piNames (Decl (Variable _ _ ident _ _)) = [ident]
|
||||
piNames (Decl (Param _ _ ident _)) = [ident]
|
||||
piNames (Decl (ParamType _ ident _)) = [ident]
|
||||
piNames (Decl (CommentDecl _)) = []
|
||||
piNames (Import x y) = [show $ Import x y]
|
||||
piNames (Export x y) = [show $ Export x y]
|
||||
piNames (Directive _) = []
|
||||
piNames (Typedef (Enum _ enumItems _) ident) =
|
||||
ident : map fst enumItems
|
||||
piNames (Typedef _ ident) = [ident]
|
||||
|
|
|
|||
|
|
@ -27,6 +27,7 @@ module Convert.Scoper
|
|||
, ScoperT
|
||||
, evalScoper
|
||||
, evalScoperT
|
||||
, runScoperT
|
||||
, partScoper
|
||||
, partScoperT
|
||||
, insertElem
|
||||
|
|
@ -36,9 +37,12 @@ module Convert.Scoper
|
|||
, Access(..)
|
||||
, ScopeKey
|
||||
, Scopes
|
||||
, extractMapping
|
||||
, embedScopes
|
||||
, withinProcedure
|
||||
, withinProcedureM
|
||||
, lookupLocalIdent
|
||||
, lookupLocalIdentM
|
||||
, scopeModuleItemT
|
||||
, Replacements
|
||||
) where
|
||||
|
|
@ -82,6 +86,12 @@ data Scopes a = Scopes
|
|||
, sInjected :: [ModuleItem]
|
||||
} deriving Show
|
||||
|
||||
extractMapping :: Scopes a -> Map.Map Identifier a
|
||||
extractMapping =
|
||||
Map.mapMaybe eElement .
|
||||
eMapping . snd .
|
||||
Map.findMin . sMapping
|
||||
|
||||
embedScopes :: Monad m => (Scopes a -> b -> c) -> b -> ScoperT a m c
|
||||
embedScopes func x = do
|
||||
scopes <- get
|
||||
|
|
@ -142,13 +152,26 @@ exprToAccesses (Dot e x) = do
|
|||
Just $ accesses ++ [Access x Nil]
|
||||
exprToAccesses _ = Nothing
|
||||
|
||||
insertElem :: Monad m => Identifier -> a -> ScoperT a m ()
|
||||
insertElem name element = do
|
||||
class ScopePath k where
|
||||
toTiers :: Scopes a -> k -> [Tier]
|
||||
|
||||
instance ScopePath Identifier where
|
||||
toTiers scopes name = sCurrent scopes ++ [Tier name ""]
|
||||
|
||||
instance ScopePath [Access] where
|
||||
toTiers _ = map toTier
|
||||
where
|
||||
toTier :: Access -> Tier
|
||||
toTier (Access x Nil) = Tier x ""
|
||||
toTier (Access x iy) = Tier x y
|
||||
where Ident y = iy
|
||||
|
||||
insertElem :: Monad m => ScopePath k => k -> a -> ScoperT a m ()
|
||||
insertElem key element = do
|
||||
s <- get
|
||||
let current = sCurrent s
|
||||
let mapping = sMapping s
|
||||
let entry = Entry (Just element) "" Map.empty
|
||||
let mapping' = setScope (current ++ [Tier name ""]) entry mapping
|
||||
let mapping' = setScope (toTiers s key) entry mapping
|
||||
put $ s { sMapping = mapping' }
|
||||
|
||||
injectItem :: Monad m => ModuleItem -> ScoperT a m ()
|
||||
|
|
@ -218,6 +241,19 @@ lookupAccesses scopes accesses = do
|
|||
let side = resolveInScope (sMapping scopes) [] accesses
|
||||
if isNothing deep then side else deep
|
||||
|
||||
lookupLocalIdent :: Scopes a -> Identifier -> LookupResult a
|
||||
lookupLocalIdent scopes ident = do
|
||||
(replacements, element) <- directResolve (sMapping scopes) accesses
|
||||
Just (accesses, replacements, element)
|
||||
where
|
||||
accesses = map toAccess (sCurrent scopes) ++ [Access ident Nil]
|
||||
toAccess :: Tier -> Access
|
||||
toAccess (Tier x "") = Access x Nil
|
||||
toAccess (Tier x y) = Access x (Ident y)
|
||||
|
||||
lookupLocalIdentM :: Monad m => Identifier -> ScoperT a m (LookupResult a)
|
||||
lookupLocalIdentM = embedScopes lookupLocalIdent
|
||||
|
||||
withinProcedureM :: Monad m => ScoperT a m Bool
|
||||
withinProcedureM = gets sProcedure
|
||||
|
||||
|
|
@ -245,8 +281,23 @@ evalScoperT
|
|||
-> Identifier
|
||||
-> [ModuleItem]
|
||||
-> m [ModuleItem]
|
||||
evalScoperT declMapper moduleItemMapper genItemMapper stmtMapper topName items =
|
||||
evalStateT operation initialState
|
||||
evalScoperT declMapper moduleItemMapper genItemMapper stmtMapper topName items = do
|
||||
(items', _) <- runScoperT
|
||||
declMapper moduleItemMapper genItemMapper stmtMapper
|
||||
topName items
|
||||
return items'
|
||||
|
||||
runScoperT
|
||||
:: 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
|
||||
-> Identifier
|
||||
-> [ModuleItem]
|
||||
-> m ([ModuleItem], Scopes a)
|
||||
runScoperT declMapper moduleItemMapper genItemMapper stmtMapper topName items =
|
||||
runStateT operation initialState
|
||||
where
|
||||
operation :: ScoperT a m [ModuleItem]
|
||||
operation = do
|
||||
|
|
|
|||
|
|
@ -613,8 +613,8 @@ traverseNodesM exprMapper declMapper typeMapper lhsMapper stmtMapper =
|
|||
return $ MIPackageItem $ Directive c
|
||||
moduleItemMapper (MIPackageItem (Import x y)) =
|
||||
return $ MIPackageItem $ Import x y
|
||||
moduleItemMapper (MIPackageItem (Export x)) =
|
||||
return $ MIPackageItem $ Export x
|
||||
moduleItemMapper (MIPackageItem (Export x y)) =
|
||||
return $ MIPackageItem $ Export x y
|
||||
moduleItemMapper (AssertionItem (mx, a)) = do
|
||||
a' <- traverseAssertionStmtsM stmtMapper a
|
||||
a'' <- traverseAssertionExprsM exprMapper a'
|
||||
|
|
@ -864,6 +864,11 @@ traverseTypeExprsM exprMapper =
|
|||
let pm' = zip (map fst pm) vals'
|
||||
rs' <- mapM (mapBothM exprMapper) rs
|
||||
return $ CSAlias ps pm' xx rs'
|
||||
typeMapper (Enum t enumItems rs) = do
|
||||
enumItems' <- mapM enumItemMapper enumItems
|
||||
rs' <- mapM (mapBothM exprMapper) rs
|
||||
return $ Enum t enumItems' rs'
|
||||
where enumItemMapper (x, e) = exprMapper e >>= \e' -> return (x, e')
|
||||
typeMapper t = do
|
||||
let (tf, rs) = typeRanges t
|
||||
rs' <- mapM (mapBothM exprMapper) rs
|
||||
|
|
|
|||
|
|
@ -12,7 +12,6 @@ module Language.SystemVerilog.AST.Description
|
|||
, Lifetime (..)
|
||||
) where
|
||||
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Text.Printf (printf)
|
||||
|
||||
import Language.SystemVerilog.AST.ShowHelp
|
||||
|
|
@ -56,8 +55,8 @@ data PackageItem
|
|||
= Typedef Type Identifier
|
||||
| Function Lifetime Type Identifier [Decl] [Stmt]
|
||||
| Task Lifetime Identifier [Decl] [Stmt]
|
||||
| Import Identifier (Maybe Identifier)
|
||||
| Export (Maybe (Identifier, Maybe Identifier))
|
||||
| Import Identifier Identifier
|
||||
| Export Identifier Identifier
|
||||
| Decl Decl
|
||||
| Directive String
|
||||
deriving Eq
|
||||
|
|
@ -70,12 +69,15 @@ instance Show PackageItem where
|
|||
show (Task ml x i b) =
|
||||
printf "task %s%s;\n%s\nendtask"
|
||||
(showPad ml) x (showBlock i b)
|
||||
show (Import x y) = printf "import %s::%s;" x (fromMaybe "*" y)
|
||||
show (Export Nothing) = "export *::*";
|
||||
show (Export (Just (x, y))) = printf "export %s::%s;" x (fromMaybe "*" y)
|
||||
show (Import x y) = printf "import %s::%s;" x (showWildcard y)
|
||||
show (Export x y) = printf "export %s::%s;" (showWildcard x) (showWildcard y)
|
||||
show (Decl decl) = show decl
|
||||
show (Directive str) = str
|
||||
|
||||
showWildcard :: Identifier -> String
|
||||
showWildcard "" = "*"
|
||||
showWildcard x = x
|
||||
|
||||
data PartKW
|
||||
= Module
|
||||
| Interface
|
||||
|
|
|
|||
|
|
@ -843,8 +843,8 @@ NonDeclPackageItem :: { [PackageItem] }
|
|||
| "function" Lifetime "void" Identifier TFItems DeclsAndStmts "endfunction" opt(Tag) { [Task $2 $4 (map defaultFuncInput $ $5 ++ fst $6) (snd $6)] }
|
||||
| "task" Lifetime Identifier TFItems DeclsAndStmts "endtask" opt(Tag) { [Task $2 $3 (map defaultFuncInput $ $4 ++ fst $5) (snd $5)] }
|
||||
| "import" PackageImportItems ";" { map (uncurry Import) $2 }
|
||||
| "export" PackageImportItems ";" { map (Export . Just) $2 }
|
||||
| "export" "*" "::" "*" ";" { [Export Nothing] } -- "Nothing" being no restrictions
|
||||
| "export" PackageImportItems ";" { map (uncurry Export) $2 }
|
||||
| "export" "*" "::" "*" ";" { [Export "" ""] }
|
||||
| ForwardTypedef ";" { $1 }
|
||||
| TimeunitsDeclaration { $1 }
|
||||
| Directive { [Directive $1] }
|
||||
|
|
@ -872,12 +872,12 @@ DefaultNetType :: { String }
|
|||
: NetType { show $1 }
|
||||
| Identifier { $1 }
|
||||
|
||||
PackageImportItems :: { [(Identifier, Maybe Identifier)] }
|
||||
PackageImportItems :: { [(Identifier, Identifier)] }
|
||||
: PackageImportItem { [$1] }
|
||||
| PackageImportItems "," PackageImportItem { $1 ++ [$3] }
|
||||
PackageImportItem :: { (Identifier, Maybe Identifier) }
|
||||
: Identifier "::" Identifier { ($1, Just $3) }
|
||||
| Identifier "::" "*" { ($1, Nothing) }
|
||||
PackageImportItem :: { (Identifier, Identifier) }
|
||||
: Identifier "::" Identifier { ($1, $3) }
|
||||
| Identifier "::" "*" { ($1, "") }
|
||||
|
||||
FuncRetAndName :: { (Type, Identifier) }
|
||||
: Type Identifier { ($1 , $2) }
|
||||
|
|
@ -987,6 +987,8 @@ StmtAsgn :: { Stmt }
|
|||
| IncOrDecOperator LHS ";" { Asgn (AsgnOp $1) Nothing $2 (RawNum 1) }
|
||||
| LHS ";" { Subroutine (lhsToExpr $1) (Args [] []) }
|
||||
| LHS CallArgs ";" { Subroutine (lhsToExpr $1) $2 }
|
||||
| Identifier "::" Identifier ";" { Subroutine (PSIdent $1 $3) (Args [] []) }
|
||||
| Identifier "::" Identifier CallArgs ";" { Subroutine (PSIdent $1 $3) $4 }
|
||||
StmtNonAsgn :: { Stmt }
|
||||
: StmtBlock(BlockKWSeq, "end" ) { $1 }
|
||||
| StmtBlock(BlockKWPar, "join") { $1 }
|
||||
|
|
|
|||
|
|
@ -81,7 +81,6 @@ executable sv2v
|
|||
Convert.LogOp
|
||||
Convert.MultiplePacked
|
||||
Convert.NamedBlock
|
||||
Convert.NestPI
|
||||
Convert.Package
|
||||
Convert.ParamNoDefault
|
||||
Convert.ParamType
|
||||
|
|
|
|||
|
|
@ -0,0 +1,18 @@
|
|||
module ExampleA;
|
||||
typedef enum logic {
|
||||
A = 1,
|
||||
B = 0,
|
||||
C = 2
|
||||
} Enum;
|
||||
Enum x = A;
|
||||
initial $display("ExampleA: x=%b, A=%b, B=%b", x, A, B);
|
||||
endmodule
|
||||
|
||||
module ExampleB;
|
||||
typedef enum logic {
|
||||
A = 0,
|
||||
B = 1
|
||||
} Enum;
|
||||
Enum x = A;
|
||||
initial $display("ExampleB: x=%b, A=%b, B=%b", x, A, B);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,14 @@
|
|||
module ExampleA;
|
||||
localparam [0:0] A = 1;
|
||||
localparam [0:0] B = 0;
|
||||
reg x = A;
|
||||
initial $display("ExampleA: x=%b, A=%b, B=%b", x, A, B);
|
||||
endmodule
|
||||
|
||||
module ExampleB;
|
||||
localparam [0:0] A = 0;
|
||||
localparam [0:0] B = 1;
|
||||
reg x = A;
|
||||
initial $display("ExampleB: x=%b, A=%b, B=%b", x, A, B);
|
||||
endmodule
|
||||
|
||||
|
|
@ -0,0 +1,4 @@
|
|||
module top;
|
||||
ExampleA a();
|
||||
ExampleB b();
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,18 @@
|
|||
package Q;
|
||||
localparam W = 5;
|
||||
localparam unrelated = 1;
|
||||
endpackage
|
||||
|
||||
package P;
|
||||
import Q::*;
|
||||
export Q::W;
|
||||
endpackage
|
||||
|
||||
module Example
|
||||
import P::*;
|
||||
(
|
||||
input logic [W - 1:0] inp
|
||||
);
|
||||
import Q::unrelated;
|
||||
initial $display("%b %0d %0d", inp, $bits(inp), unrelated);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,6 @@
|
|||
module Example(inp);
|
||||
localparam W = 5;
|
||||
localparam unrelated = 1;
|
||||
input wire [W - 1:0] inp;
|
||||
initial $display("%b %0d %0d", inp, $bits(inp), unrelated);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,3 @@
|
|||
module top;
|
||||
Example e(5'b00000);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,11 @@
|
|||
package Pkg;
|
||||
localparam integer X = func(1);
|
||||
function automatic integer func;
|
||||
input integer inp;
|
||||
func = inp * 2;
|
||||
endfunction
|
||||
endpackage
|
||||
|
||||
module top;
|
||||
initial $display(Pkg::X);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,8 @@
|
|||
module top;
|
||||
function automatic integer func;
|
||||
input integer inp;
|
||||
func = inp * 2;
|
||||
endfunction
|
||||
localparam integer X = func(1);
|
||||
initial $display(X);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,13 @@
|
|||
package P;
|
||||
localparam X = 1;
|
||||
localparam Y = 2;
|
||||
typedef enum {
|
||||
A = X,
|
||||
B = Y
|
||||
} Enum;
|
||||
endpackage
|
||||
|
||||
module top;
|
||||
import P::*;
|
||||
initial $display("%0d %0d %0d", X, A, B);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,7 @@
|
|||
module top;
|
||||
localparam X = 1;
|
||||
localparam Y = 2;
|
||||
localparam A = X;
|
||||
localparam B = Y;
|
||||
initial $display("%0d %0d %0d", X, A, B);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,10 @@
|
|||
package PkgA;
|
||||
localparam Foo = 1;
|
||||
endpackage
|
||||
package PkgB;
|
||||
export PkgA::*;
|
||||
localparam Bar = 2;
|
||||
endpackage
|
||||
module top;
|
||||
initial $display(PkgB::Bar);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,4 @@
|
|||
module top;
|
||||
localparam Bar = 2;
|
||||
initial $display(Bar);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,23 @@
|
|||
package P;
|
||||
localparam X = 1;
|
||||
endpackage
|
||||
package Q;
|
||||
import P::X;
|
||||
export P::*;
|
||||
localparam Y = 2;
|
||||
endpackage
|
||||
package R;
|
||||
import Q::X;
|
||||
export Q::*;
|
||||
localparam Z = 3;
|
||||
endpackage
|
||||
package S;
|
||||
import P::X;
|
||||
import Q::Y;
|
||||
import R::Z;
|
||||
export *::*;
|
||||
endpackage
|
||||
module top;
|
||||
import S::*;
|
||||
initial $display(X, Y, Z);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,6 @@
|
|||
module top;
|
||||
localparam X = 1;
|
||||
localparam Y = 2;
|
||||
localparam Z = 3;
|
||||
initial $display(X, Y, Z);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,14 @@
|
|||
package PkgA;
|
||||
localparam X = 1;
|
||||
localparam Y = 2;
|
||||
endpackage
|
||||
package PkgB;
|
||||
localparam X = 3;
|
||||
localparam Z = 4;
|
||||
endpackage
|
||||
import PkgA::*;
|
||||
import PkgB::*;
|
||||
localparam X = 5;
|
||||
module top;
|
||||
initial $display(X, Y, Z);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,6 @@
|
|||
module top;
|
||||
localparam X = 5;
|
||||
localparam Y = 2;
|
||||
localparam Z = 4;
|
||||
initial $display(X, Y, Z);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,172 @@
|
|||
`define DUMP(key) initial $display(`"key %0d`", X);
|
||||
|
||||
package P;
|
||||
localparam X = 1;
|
||||
endpackage
|
||||
|
||||
package Q;
|
||||
localparam X = 2;
|
||||
endpackage
|
||||
|
||||
module ExampleA;
|
||||
import P::*;
|
||||
localparam X = 3;
|
||||
`DUMP(A)
|
||||
endmodule
|
||||
|
||||
module ExampleB;
|
||||
localparam X = 3;
|
||||
import P::*;
|
||||
`DUMP(B)
|
||||
endmodule
|
||||
|
||||
module ExampleC;
|
||||
import P::*;
|
||||
`DUMP(C)
|
||||
endmodule
|
||||
|
||||
module ExampleD;
|
||||
import Q::*;
|
||||
`DUMP(D)
|
||||
endmodule
|
||||
|
||||
module ExampleE;
|
||||
import P::*;
|
||||
import Q::X;
|
||||
`DUMP(E)
|
||||
endmodule
|
||||
|
||||
module ExampleF;
|
||||
import Q::X;
|
||||
import P::*;
|
||||
`DUMP(F)
|
||||
endmodule
|
||||
|
||||
module ExampleG;
|
||||
import P::*;
|
||||
import Q::*;
|
||||
// allowed but can't reference C
|
||||
endmodule
|
||||
|
||||
package R;
|
||||
import P::X;
|
||||
export P::X;
|
||||
endpackage
|
||||
|
||||
package S;
|
||||
import P::X;
|
||||
export R::X; // oof but it's allowed
|
||||
endpackage
|
||||
|
||||
module ExampleH;
|
||||
import R::*;
|
||||
import S::*;
|
||||
`DUMP(H)
|
||||
endmodule
|
||||
|
||||
module ExampleI;
|
||||
import R::X;
|
||||
import S::X;
|
||||
`DUMP(I)
|
||||
endmodule
|
||||
|
||||
module ExampleJ;
|
||||
import R::*;
|
||||
`DUMP(J)
|
||||
import S::X;
|
||||
endmodule
|
||||
|
||||
module ExampleK;
|
||||
import P::X;
|
||||
if (1) begin : blk1
|
||||
import P::X;
|
||||
`DUMP(K1)
|
||||
end
|
||||
if (1) begin : blk2
|
||||
import Q::X;
|
||||
`DUMP(K2)
|
||||
end
|
||||
if (1) begin : blk3
|
||||
localparam X = 3;
|
||||
`DUMP(K3)
|
||||
end
|
||||
if (1) begin : blk4
|
||||
import Q::*;
|
||||
`DUMP(K4)
|
||||
end
|
||||
`DUMP(K0)
|
||||
endmodule
|
||||
|
||||
module ExampleL;
|
||||
import P::X;
|
||||
import R::X;
|
||||
`DUMP(L)
|
||||
endmodule
|
||||
|
||||
package T;
|
||||
import P::X;
|
||||
export P::*;
|
||||
endpackage
|
||||
|
||||
package U;
|
||||
import P::*;
|
||||
export P::X;
|
||||
endpackage
|
||||
|
||||
package V;
|
||||
import P::*;
|
||||
export P::*;
|
||||
localparam Y = X;
|
||||
endpackage
|
||||
|
||||
package W;
|
||||
import P::*;
|
||||
export P::*;
|
||||
task help;
|
||||
$display("W::help() %0d", X);
|
||||
endtask
|
||||
endpackage
|
||||
|
||||
module ExampleM;
|
||||
if (1) begin : blk1
|
||||
import T::X;
|
||||
`DUMP(M1)
|
||||
end
|
||||
if (1) begin : blk2
|
||||
import U::X;
|
||||
`DUMP(M2)
|
||||
end
|
||||
if (1) begin : blk3
|
||||
import V::X;
|
||||
`DUMP(M3)
|
||||
end
|
||||
if (1) begin : blk4
|
||||
import W::X;
|
||||
`DUMP(M4)
|
||||
initial W::help;
|
||||
initial W::help();
|
||||
end
|
||||
endmodule
|
||||
|
||||
module ExampleN;
|
||||
import P::*;
|
||||
if (1) begin : blk1
|
||||
import P::X;
|
||||
`DUMP(N1)
|
||||
end
|
||||
import Q::X;
|
||||
`DUMP(N2)
|
||||
endmodule
|
||||
|
||||
module ExampleO;
|
||||
import P::*;
|
||||
if (1) begin : blk1
|
||||
import P::*;
|
||||
`DUMP(O1)
|
||||
end
|
||||
import Q::X;
|
||||
`DUMP(O2)
|
||||
endmodule
|
||||
|
||||
module top;
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,30 @@
|
|||
module top;
|
||||
initial begin
|
||||
$display("A 3");
|
||||
$display("B 3");
|
||||
$display("C 1");
|
||||
$display("D 2");
|
||||
$display("E 2");
|
||||
$display("F 2");
|
||||
// G doesn't print
|
||||
$display("H 1");
|
||||
$display("I 1");
|
||||
$display("J 1");
|
||||
$display("K1 1");
|
||||
$display("K2 2");
|
||||
$display("K3 3");
|
||||
$display("K4 2");
|
||||
$display("K0 1");
|
||||
$display("L 1");
|
||||
$display("M1 1");
|
||||
$display("M2 1");
|
||||
$display("M3 1");
|
||||
$display("M4 1");
|
||||
$display("W::help() 1");
|
||||
$display("W::help() 1");
|
||||
$display("N1 1");
|
||||
$display("N2 2");
|
||||
$display("O1 1");
|
||||
$display("O2 2");
|
||||
end
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,9 @@
|
|||
// pattern: invalid export Pkg::Foo outside of package
|
||||
package Pkg;
|
||||
localparam Foo = 1;
|
||||
endpackage
|
||||
import Pkg::Foo;
|
||||
export Pkg::Foo;
|
||||
module top;
|
||||
initial $display(Foo);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,9 @@
|
|||
// pattern: invalid export Pkg::Foo outside of package
|
||||
package Pkg;
|
||||
localparam Foo = 1;
|
||||
endpackage
|
||||
module top;
|
||||
import Pkg::Foo;
|
||||
export Pkg::Foo;
|
||||
initial $display(Foo);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,9 @@
|
|||
// pattern: invalid export \*::\* outside of package
|
||||
package Pkg;
|
||||
localparam Foo = 1;
|
||||
endpackage
|
||||
import Pkg::Foo;
|
||||
export *::*;
|
||||
module top;
|
||||
initial $display(Foo);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,4 @@
|
|||
// pattern: could not find package "PackageThatDoesNotExist"
|
||||
module top;
|
||||
import PackageThatDoesNotExist::*;
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,9 @@
|
|||
// pattern: could not find "ItemThatDoesNotExist" in package "Pkg"
|
||||
|
||||
package Pkg;
|
||||
localparam Foo = 1;
|
||||
endpackage
|
||||
|
||||
module top;
|
||||
import Pkg::ItemThatDoesNotExist;
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,12 @@
|
|||
// pattern: could not find "X" in package "Q"
|
||||
package P;
|
||||
localparam X = 1;
|
||||
endpackage
|
||||
package Q;
|
||||
import P::*;
|
||||
export P::*;
|
||||
localparam Y = P::X;
|
||||
endpackage
|
||||
module top;
|
||||
initial $display(Q::X);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,13 @@
|
|||
// pattern: could not find "X" in package "Q"
|
||||
package P;
|
||||
localparam X = 1;
|
||||
localparam Y = 2;
|
||||
endpackage
|
||||
package Q;
|
||||
import P::*;
|
||||
export *::*;
|
||||
localparam Z = P::Y;
|
||||
endpackage
|
||||
module top;
|
||||
initial $display(Q::X);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,11 @@
|
|||
// pattern: export of PkgA::Bar, but Bar was never imported
|
||||
package PkgA;
|
||||
localparam Bar = 2;
|
||||
endpackage
|
||||
package PkgB;
|
||||
export PkgA::Bar;
|
||||
localparam Foo = 1;
|
||||
endpackage
|
||||
module top;
|
||||
initial $display(PkgB::Foo);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,16 @@
|
|||
// pattern: export of Bar::Foo differs from import of Foo::Foo
|
||||
package Bar;
|
||||
localparam Bar = 1;
|
||||
localparam Foo = 3;
|
||||
endpackage
|
||||
package Foo;
|
||||
localparam Foo = 2;
|
||||
endpackage
|
||||
package Pkg;
|
||||
import Foo::Foo;
|
||||
import Bar::Bar;
|
||||
export Bar::Foo;
|
||||
endpackage
|
||||
module top;
|
||||
initial $display(Pkg::Foo);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,11 @@
|
|||
// pattern: could not find "Foo" in package "Bar"
|
||||
package Bar;
|
||||
localparam Bar = 1;
|
||||
endpackage
|
||||
package Pkg;
|
||||
import Bar::*;
|
||||
export Bar::Foo;
|
||||
endpackage
|
||||
module top;
|
||||
initial $display(Pkg::Foo);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,10 @@
|
|||
// pattern: could not find package "PackageThatDoesNotExist"
|
||||
|
||||
package Wrap;
|
||||
import PackageThatDoesNotExist::*;
|
||||
localparam Foo = Bar;
|
||||
endpackage
|
||||
|
||||
module top;
|
||||
import Wrap::*;
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,13 @@
|
|||
// pattern: could not find "ItemThatDoesNotExist" in package "Pkg"
|
||||
|
||||
package Pkg;
|
||||
localparam Foo = 1;
|
||||
endpackage
|
||||
|
||||
package Wrap;
|
||||
localparam Foo = Pkg::ItemThatDoesNotExist;
|
||||
endpackage
|
||||
|
||||
module top;
|
||||
import Wrap::*;
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,12 @@
|
|||
// pattern: package dependency loop: "PkgA" depends on "PkgB", which depends on "PkgA"
|
||||
package PkgA;
|
||||
import PkgB::Foo;
|
||||
export PkgB::Foo;
|
||||
endpackage
|
||||
package PkgB;
|
||||
import PkgA::Foo;
|
||||
export PkgA::Foo;
|
||||
endpackage
|
||||
module top;
|
||||
initial $display(PkgA::Foo);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,16 @@
|
|||
// pattern: package dependency loop: "PkgA" depends on "PkgC", which depends on "PkgB", which depends on "PkgA"
|
||||
package PkgA;
|
||||
import PkgC::Foo;
|
||||
export PkgC::Foo;
|
||||
endpackage
|
||||
package PkgB;
|
||||
import PkgA::Foo;
|
||||
export PkgA::Foo;
|
||||
endpackage
|
||||
package PkgC;
|
||||
import PkgB::Foo;
|
||||
export PkgB::Foo;
|
||||
endpackage
|
||||
module top;
|
||||
initial $display(PkgA::Foo);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,12 @@
|
|||
// pattern: identifier "X" ambiguously refers to the definitions in any of P, Q
|
||||
package P;
|
||||
localparam X = 1;
|
||||
endpackage
|
||||
package Q;
|
||||
localparam X = 2;
|
||||
endpackage
|
||||
module top;
|
||||
import P::*;
|
||||
import Q::*;
|
||||
initial $display(X);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,11 @@
|
|||
// pattern: import of Q::X conflicts with prior import of P::X
|
||||
package P;
|
||||
localparam X = 1;
|
||||
endpackage
|
||||
package Q;
|
||||
localparam X = 2;
|
||||
endpackage
|
||||
module top;
|
||||
import P::X;
|
||||
import Q::X;
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,8 @@
|
|||
// pattern: declaration of X conflicts with prior import of P::X
|
||||
package P;
|
||||
localparam X = 1;
|
||||
endpackage
|
||||
module top;
|
||||
import P::X;
|
||||
localparam X = 2;
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,8 @@
|
|||
// pattern: import of P::X conflicts with prior declaration of X
|
||||
package P;
|
||||
localparam X = 1;
|
||||
endpackage
|
||||
module top;
|
||||
localparam X = 2;
|
||||
import P::X;
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,12 @@
|
|||
// pattern: import of P::X conflicts with prior import of Q::X
|
||||
package P;
|
||||
localparam X = 1;
|
||||
endpackage
|
||||
package Q;
|
||||
localparam X = 2;
|
||||
endpackage
|
||||
module top;
|
||||
import Q::*;
|
||||
initial $display(X); // imports Q::X
|
||||
import P::X; // illegal
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,19 @@
|
|||
// pattern: import of Q::X conflicts with prior import of P::X
|
||||
package P;
|
||||
localparam X = 1;
|
||||
endpackage
|
||||
package Q;
|
||||
localparam X = 2;
|
||||
endpackage
|
||||
package W;
|
||||
import P::*;
|
||||
export P::*;
|
||||
task help;
|
||||
$display("W::help() %0d", X);
|
||||
endtask
|
||||
import Q::X;
|
||||
endpackage
|
||||
module top;
|
||||
import W::*;
|
||||
initial $display(X);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,15 @@
|
|||
// pattern: import of Q::X conflicts with prior import of P::X
|
||||
package P;
|
||||
localparam X = 1;
|
||||
endpackage
|
||||
package Q;
|
||||
localparam X = 2;
|
||||
endpackage
|
||||
module top;
|
||||
import P::*;
|
||||
if (1) begin : blk1
|
||||
// forces import of P::X at the top level
|
||||
initial $display(X);
|
||||
end
|
||||
import Q::X; // illegal
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,12 @@
|
|||
// pattern: identifier "X" ambiguously refers to the definitions in any of PkgA, PkgB
|
||||
package PkgA;
|
||||
localparam X = 1;
|
||||
endpackage
|
||||
package PkgB;
|
||||
localparam X = 3;
|
||||
endpackage
|
||||
import PkgA::*;
|
||||
import PkgB::*;
|
||||
module top;
|
||||
initial $display(X);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,8 @@
|
|||
// pattern: package dependency loop: "Pkg" depends on "Pkg"
|
||||
package Pkg;
|
||||
localparam Foo = 1;
|
||||
export Pkg::Foo;
|
||||
endpackage
|
||||
module top;
|
||||
initial $display(Pkg::Foo);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,9 @@
|
|||
// pattern: package dependency loop: "P" depends on "P"
|
||||
package P;
|
||||
import P::*;
|
||||
localparam Foo = 1;
|
||||
endpackage
|
||||
module top;
|
||||
import P::*;
|
||||
initial $display(Foo);
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,8 @@
|
|||
// pattern: package dependency loop: "P" depends on "P"
|
||||
package P;
|
||||
localparam Foo = P::Foo;
|
||||
endpackage
|
||||
module top;
|
||||
import P::*;
|
||||
initial $display(Foo);
|
||||
endmodule
|
||||
Loading…
Reference in New Issue