mirror of https://github.com/zachjs/sv2v.git
conversions are applied per-file
- NestTF refactored to cover all package items - fixed issue where type traverse skipped typedefs
This commit is contained in:
parent
da38776d73
commit
33dc4b3f88
|
|
@ -19,7 +19,7 @@ import qualified Convert.Interface
|
|||
import qualified Convert.KWArgs
|
||||
import qualified Convert.Logic
|
||||
import qualified Convert.NamedBlock
|
||||
import qualified Convert.NestTF
|
||||
import qualified Convert.NestPI
|
||||
import qualified Convert.PackedArray
|
||||
import qualified Convert.Return
|
||||
import qualified Convert.StarPort
|
||||
|
|
@ -29,7 +29,7 @@ import qualified Convert.Typedef
|
|||
import qualified Convert.UnbasedUnsized
|
||||
import qualified Convert.Unique
|
||||
|
||||
type Phase = AST -> AST
|
||||
type Phase = [AST] -> [AST]
|
||||
|
||||
phases :: [Job.Exclude] -> [Phase]
|
||||
phases excludes =
|
||||
|
|
@ -49,9 +49,9 @@ phases excludes =
|
|||
, Convert.Typedef.convert
|
||||
, Convert.UnbasedUnsized.convert
|
||||
, Convert.Unique.convert
|
||||
, Convert.NestPI.convert
|
||||
, selectExclude (Job.Interface, Convert.Interface.convert)
|
||||
, selectExclude (Job.Always , Convert.AlwaysKW.convert)
|
||||
, Convert.NestTF.convert
|
||||
]
|
||||
where
|
||||
selectExclude :: (Job.Exclude, Phase) -> Phase
|
||||
|
|
|
|||
|
|
@ -12,8 +12,8 @@ module Convert.AlwaysKW (convert) where
|
|||
import Convert.Traverse
|
||||
import Language.SystemVerilog.AST
|
||||
|
||||
convert :: AST -> AST
|
||||
convert = traverseDescriptions $ traverseModuleItems replaceAlwaysKW
|
||||
convert :: [AST] -> [AST]
|
||||
convert = map $ traverseDescriptions $ traverseModuleItems replaceAlwaysKW
|
||||
|
||||
replaceAlwaysKW :: ModuleItem -> ModuleItem
|
||||
replaceAlwaysKW (AlwaysC AlwaysComb stmt) =
|
||||
|
|
|
|||
|
|
@ -11,9 +11,9 @@ module Convert.AsgnOp (convert) where
|
|||
import Convert.Traverse
|
||||
import Language.SystemVerilog.AST
|
||||
|
||||
convert :: AST -> AST
|
||||
convert :: [AST] -> [AST]
|
||||
convert =
|
||||
traverseDescriptions $ traverseModuleItems $
|
||||
map $ traverseDescriptions $ traverseModuleItems $
|
||||
( traverseStmts convertStmt
|
||||
. traverseGenItems convertGenItem
|
||||
)
|
||||
|
|
|
|||
|
|
@ -9,8 +9,8 @@ module Convert.Assertion (convert) where
|
|||
import Convert.Traverse
|
||||
import Language.SystemVerilog.AST
|
||||
|
||||
convert :: AST -> AST
|
||||
convert = traverseDescriptions $ traverseModuleItems convertModuleItem
|
||||
convert :: [AST] -> [AST]
|
||||
convert = map $ traverseDescriptions $ traverseModuleItems convertModuleItem
|
||||
|
||||
convertModuleItem :: ModuleItem -> ModuleItem
|
||||
convertModuleItem (AssertionItem item) =
|
||||
|
|
|
|||
|
|
@ -24,8 +24,8 @@ import Language.SystemVerilog.AST
|
|||
|
||||
type Info = Map.Map Identifier (Type, [Range])
|
||||
|
||||
convert :: AST -> AST
|
||||
convert = traverseDescriptions convertDescription
|
||||
convert :: [AST] -> [AST]
|
||||
convert = map $ traverseDescriptions convertDescription
|
||||
|
||||
convertDescription :: Description -> Description
|
||||
convertDescription =
|
||||
|
|
|
|||
|
|
@ -33,8 +33,8 @@ type Enums = Set.Set EnumInfo
|
|||
type Idents = Set.Set Identifier
|
||||
type EnumItem = ((Range, Identifier), Expr)
|
||||
|
||||
convert :: AST -> AST
|
||||
convert = traverseDescriptions convertDescription
|
||||
convert :: [AST] -> [AST]
|
||||
convert = map $ traverseDescriptions convertDescription
|
||||
|
||||
defaultType :: Type
|
||||
defaultType = IntegerVector TLogic Unspecified [(Number "31", Number "0")]
|
||||
|
|
|
|||
|
|
@ -12,8 +12,8 @@ module Convert.FuncRet (convert) where
|
|||
import Convert.Traverse
|
||||
import Language.SystemVerilog.AST
|
||||
|
||||
convert :: AST -> AST
|
||||
convert = traverseDescriptions $ traverseModuleItems convertFunction
|
||||
convert :: [AST] -> [AST]
|
||||
convert = map $ traverseDescriptions $ traverseModuleItems convertFunction
|
||||
|
||||
convertFunction :: ModuleItem -> ModuleItem
|
||||
convertFunction (MIPackageItem (Function ml t f decls stmts)) =
|
||||
|
|
|
|||
|
|
@ -20,14 +20,15 @@ type Interfaces = Map.Map Identifier Interface
|
|||
type Modports = Map.Map Identifier [ModportDecl]
|
||||
type Modules = Map.Map (Identifier, Identifier) Type
|
||||
|
||||
convert :: AST -> AST
|
||||
convert :: [AST] -> [AST]
|
||||
convert descriptions =
|
||||
filter (not . isInterface) $
|
||||
traverseDescriptions (convertDescription interfaces modules) $
|
||||
descriptions
|
||||
map (
|
||||
filter (not . isInterface) .
|
||||
traverseDescriptions (convertDescription interfaces modules)
|
||||
) descriptions
|
||||
where
|
||||
(interfaces, modules) =
|
||||
execWriter $ collectDescriptionsM collectDesc descriptions
|
||||
execWriter $ collectDescriptionsM collectDesc $ concat descriptions
|
||||
-- we can only collect/map non-extern interfaces
|
||||
collectDesc :: Description -> Writer (Interfaces, Modules) ()
|
||||
collectDesc (orig @ (Part False kw _ name ports items)) = do
|
||||
|
|
|
|||
|
|
@ -19,8 +19,8 @@ import Language.SystemVerilog.AST
|
|||
|
||||
type TFs = Map.Map Identifier [Identifier]
|
||||
|
||||
convert :: AST -> AST
|
||||
convert = traverseDescriptions convertDescription
|
||||
convert :: [AST] -> [AST]
|
||||
convert = map $ traverseDescriptions convertDescription
|
||||
|
||||
convertDescription :: Description -> Description
|
||||
convertDescription description =
|
||||
|
|
|
|||
|
|
@ -33,11 +33,11 @@ import Language.SystemVerilog.AST
|
|||
type Idents = Set.Set Identifier
|
||||
type Ports = Map.Map (Identifier, Identifier) Direction
|
||||
|
||||
convert :: AST -> AST
|
||||
convert ast =
|
||||
traverseDescriptions (convertDescription ports) ast
|
||||
convert :: [AST] -> [AST]
|
||||
convert asts =
|
||||
map (traverseDescriptions $ convertDescription ports) asts
|
||||
where
|
||||
ports = execWriter $ collectDescriptionsM collectPortsM ast
|
||||
ports = execWriter $ collectDescriptionsM collectPortsM $ concat asts
|
||||
collectPortsM :: Description -> Writer Ports ()
|
||||
collectPortsM (orig @ (Part _ _ _ name portNames _)) =
|
||||
collectModuleItemsM collectPortDirsM orig
|
||||
|
|
|
|||
|
|
@ -18,12 +18,12 @@ import Language.SystemVerilog.AST
|
|||
|
||||
type Idents = Set.Set Identifier
|
||||
|
||||
convert :: AST -> AST
|
||||
convert ast =
|
||||
convert :: [AST] -> [AST]
|
||||
convert asts =
|
||||
-- we collect all the existing blocks in the first pass to make sure we
|
||||
-- don't generate conflicting names on repeated passes of this conversion
|
||||
evalState (runner collectStmtM ast >>= runner traverseStmtM) Set.empty
|
||||
where runner = traverseDescriptionsM . traverseModuleItemsM . traverseStmtsM
|
||||
evalState (runner collectStmtM asts >>= runner traverseStmtM) Set.empty
|
||||
where runner = mapM . traverseDescriptionsM . traverseModuleItemsM . traverseStmtsM
|
||||
|
||||
collectStmtM :: Stmt -> State Idents Stmt
|
||||
collectStmtM (Block (Just x) decls stmts) = do
|
||||
|
|
|
|||
|
|
@ -0,0 +1,96 @@
|
|||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-
|
||||
- Conversion for moving top-level package items into modules
|
||||
-}
|
||||
|
||||
module Convert.NestPI (convert) where
|
||||
|
||||
import Control.Monad.State
|
||||
import Control.Monad.Writer
|
||||
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 asts =
|
||||
map (filter (not . isPI) . nest) asts
|
||||
where
|
||||
nest :: AST -> AST
|
||||
nest curr =
|
||||
if next == curr
|
||||
then curr
|
||||
else nest next
|
||||
where
|
||||
next = evalState (traverseM curr) Map.empty
|
||||
traverseM = traverseDescriptionsM traverseDescriptionM
|
||||
isPI :: Description -> Bool
|
||||
isPI (PackageItem item) = piName item /= Nothing
|
||||
isPI _ = False
|
||||
|
||||
-- collects and nests in tasks and functions missing from modules
|
||||
traverseDescriptionM :: Description -> State PIs Description
|
||||
traverseDescriptionM (PackageItem item) = do
|
||||
() <- case piName item of
|
||||
Nothing -> return ()
|
||||
Just ident -> modify $ Map.insert ident item
|
||||
return $ PackageItem item
|
||||
traverseDescriptionM (orig @ (Part extern kw lifetime name ports items)) = do
|
||||
tfs <- get
|
||||
let newItems = map MIPackageItem $ Map.elems $
|
||||
Map.restrictKeys tfs neededPIs
|
||||
return $ Part extern kw lifetime name ports (items ++ newItems)
|
||||
where
|
||||
existingPIs = execWriter $ collectModuleItemsM collectPIsM orig
|
||||
runner f = execWriter $ collectModuleItemsM f orig
|
||||
usedPIs = Set.unions $ map runner $
|
||||
[ collectStmtsM collectSubroutinesM
|
||||
, collectTypesM collectTypenamesM
|
||||
, collectExprsM $ collectNestedExprsM collectIdentsM
|
||||
]
|
||||
neededPIs = Set.difference usedPIs existingPIs
|
||||
traverseDescriptionM other = return other
|
||||
|
||||
-- writes down the names of package items
|
||||
collectPIsM :: ModuleItem -> Writer Idents ()
|
||||
collectPIsM (MIPackageItem item) =
|
||||
case piName item of
|
||||
Nothing -> return ()
|
||||
Just ident -> tell $ Set.singleton ident
|
||||
collectPIsM _ = return ()
|
||||
|
||||
-- writes down the names of subroutine invocations
|
||||
collectSubroutinesM :: Stmt -> Writer Idents ()
|
||||
collectSubroutinesM (Subroutine f _) = tell $ Set.singleton f
|
||||
collectSubroutinesM _ = return ()
|
||||
|
||||
-- writes down the names of function calls and identifiers
|
||||
collectIdentsM :: Expr -> Writer Idents ()
|
||||
collectIdentsM (Call x _) = tell $ Set.singleton x
|
||||
collectIdentsM (Ident x ) = tell $ Set.singleton x
|
||||
collectIdentsM _ = return ()
|
||||
|
||||
-- writes down aliased typenames
|
||||
collectTypenamesM :: Type -> Writer Idents ()
|
||||
collectTypenamesM (Alias x _) = tell $ Set.singleton x
|
||||
collectTypenamesM (Enum (Just t) _ _) = collectTypenamesM t
|
||||
collectTypenamesM (Struct _ fields _) = do
|
||||
_ <- mapM collectTypenamesM $ map fst fields
|
||||
return ()
|
||||
collectTypenamesM _ = return ()
|
||||
|
||||
-- returns the "name" of a package item, if it has one
|
||||
piName :: PackageItem -> Maybe Identifier
|
||||
piName (Function _ _ ident _ _) = Just ident
|
||||
piName (Task _ ident _ _) = Just ident
|
||||
piName (Typedef _ ident ) = Just ident
|
||||
piName (Decl (Variable _ _ ident _ _)) = Just ident
|
||||
piName (Decl (Parameter _ ident _)) = Just ident
|
||||
piName (Decl (Localparam _ ident _)) = Just ident
|
||||
piName (Import _ _) = Nothing
|
||||
piName (Comment _) = Nothing
|
||||
|
|
@ -1,75 +0,0 @@
|
|||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-
|
||||
- Conversion for moving top-level tasks and functions into modules
|
||||
-}
|
||||
|
||||
module Convert.NestTF (convert) where
|
||||
|
||||
import Control.Monad.State
|
||||
import Control.Monad.Writer
|
||||
import qualified Data.Map.Strict as Map
|
||||
import qualified Data.Set as Set
|
||||
|
||||
import Convert.Traverse
|
||||
import Language.SystemVerilog.AST
|
||||
|
||||
type TFs = Map.Map Identifier PackageItem
|
||||
type Idents = Set.Set Identifier
|
||||
|
||||
convert :: AST -> AST
|
||||
convert ast =
|
||||
filter (not . isTF) $ nest $ ast
|
||||
where
|
||||
nest :: AST -> AST
|
||||
nest curr =
|
||||
if next == curr
|
||||
then curr
|
||||
else nest next
|
||||
where
|
||||
next = evalState (traverseM curr) Map.empty
|
||||
traverseM = traverseDescriptionsM traverseDescriptionM
|
||||
isTF :: Description -> Bool
|
||||
isTF (PackageItem (Function _ _ _ _ _)) = True
|
||||
isTF (PackageItem (Task _ _ _ _)) = True
|
||||
isTF _ = False
|
||||
|
||||
-- collects and nests in tasks and functions missing from modules
|
||||
traverseDescriptionM :: Description -> State TFs Description
|
||||
traverseDescriptionM (PackageItem item) = do
|
||||
() <- case item of
|
||||
Function _ _ ident _ _ -> modify $ Map.insert ident item
|
||||
Task _ ident _ _ -> modify $ Map.insert ident item
|
||||
_ -> return ()
|
||||
return $ PackageItem item
|
||||
traverseDescriptionM (orig @ (Part extern kw lifetime name ports items)) = do
|
||||
tfs <- get
|
||||
let newItems = map MIPackageItem $ Map.elems $
|
||||
Map.restrictKeys tfs neededTFs
|
||||
return $ Part extern kw lifetime name ports (items ++ newItems)
|
||||
where
|
||||
existingTFs = execWriter $ collectModuleItemsM collectTFsM orig
|
||||
usedTFs = Set.union
|
||||
(execWriter $ collectModuleItemsM (collectStmtsM collectSubroutinesM) orig)
|
||||
(execWriter $ collectModuleItemsM (collectExprsM $ collectNestedExprsM collectCallsM) orig)
|
||||
neededTFs = Set.difference usedTFs existingTFs
|
||||
traverseDescriptionM other = return other
|
||||
|
||||
-- writes down the names of tasks and functions
|
||||
collectTFsM :: ModuleItem -> Writer Idents ()
|
||||
collectTFsM (MIPackageItem item) =
|
||||
case item of
|
||||
Function _ _ ident _ _ -> tell $ Set.singleton ident
|
||||
Task _ ident _ _ -> tell $ Set.singleton ident
|
||||
_ -> return ()
|
||||
collectTFsM _ = return ()
|
||||
|
||||
-- writes down the names of subroutine invocations
|
||||
collectSubroutinesM :: Stmt -> Writer Idents ()
|
||||
collectSubroutinesM (Subroutine f _) = tell $ Set.singleton f
|
||||
collectSubroutinesM _ = return ()
|
||||
|
||||
-- writes down the names of function calls
|
||||
collectCallsM :: Expr -> Writer Idents ()
|
||||
collectCallsM (Call f _) = tell $ Set.singleton f
|
||||
collectCallsM _ = return ()
|
||||
|
|
@ -31,8 +31,8 @@ data Info = Info
|
|||
{ sTypeDims :: DimMap
|
||||
} deriving (Eq, Show)
|
||||
|
||||
convert :: AST -> AST
|
||||
convert = traverseDescriptions convertDescription
|
||||
convert :: [AST] -> [AST]
|
||||
convert = map $ traverseDescriptions convertDescription
|
||||
|
||||
convertDescription :: Description -> Description
|
||||
convertDescription =
|
||||
|
|
|
|||
|
|
@ -9,8 +9,8 @@ module Convert.Return (convert) where
|
|||
import Convert.Traverse
|
||||
import Language.SystemVerilog.AST
|
||||
|
||||
convert :: AST -> AST
|
||||
convert = traverseDescriptions $ traverseModuleItems convertFunction
|
||||
convert :: [AST] -> [AST]
|
||||
convert = map $ traverseDescriptions $ traverseModuleItems convertFunction
|
||||
|
||||
convertFunction :: ModuleItem -> ModuleItem
|
||||
convertFunction (MIPackageItem (Function ml t f decls stmts)) =
|
||||
|
|
|
|||
|
|
@ -12,11 +12,11 @@ import qualified Data.Map.Strict as Map
|
|||
import Convert.Traverse
|
||||
import Language.SystemVerilog.AST
|
||||
|
||||
convert :: AST -> AST
|
||||
convert descriptions =
|
||||
traverseDescriptions (traverseModuleItems mapInstance) descriptions
|
||||
convert :: [AST] -> [AST]
|
||||
convert asts =
|
||||
map (traverseDescriptions $ traverseModuleItems mapInstance) asts
|
||||
where
|
||||
modulePorts = execWriter $ collectDescriptionsM getPorts descriptions
|
||||
modulePorts = execWriter $ collectDescriptionsM getPorts $ concat asts
|
||||
getPorts :: Description -> Writer (Map.Map Identifier [Identifier]) ()
|
||||
getPorts (Part _ _ _ name ports _) = tell $ Map.singleton name ports
|
||||
getPorts _ = return ()
|
||||
|
|
|
|||
|
|
@ -10,8 +10,8 @@ module Convert.StmtBlock (convert) where
|
|||
import Convert.Traverse
|
||||
import Language.SystemVerilog.AST
|
||||
|
||||
convert :: AST -> AST
|
||||
convert = traverseDescriptions $ traverseModuleItems convertModuleItem
|
||||
convert :: [AST] -> [AST]
|
||||
convert = map $ traverseDescriptions $ traverseModuleItems convertModuleItem
|
||||
|
||||
convertModuleItem :: ModuleItem -> ModuleItem
|
||||
convertModuleItem (MIPackageItem packageItem) =
|
||||
|
|
|
|||
|
|
@ -24,8 +24,8 @@ type Structs = Map.Map TypeFunc StructInfo
|
|||
type Types = Map.Map Identifier Type
|
||||
type Idents = Set.Set Identifier
|
||||
|
||||
convert :: AST -> AST
|
||||
convert = traverseDescriptions convertDescription
|
||||
convert :: [AST] -> [AST]
|
||||
convert = map $ traverseDescriptions convertDescription
|
||||
|
||||
convertDescription :: Description -> Description
|
||||
convertDescription (description @ (Part _ _ _ _ _ _)) =
|
||||
|
|
|
|||
|
|
@ -562,8 +562,8 @@ traverseExprsM' strat exprMapper = moduleItemMapper
|
|||
return $ MIPackageItem $ Typedef t x
|
||||
moduleItemMapper (MIPackageItem (Comment c)) =
|
||||
return $ MIPackageItem $ Comment c
|
||||
moduleItemMapper (MIPackageItem (Import imports)) =
|
||||
return $ MIPackageItem $ Import imports
|
||||
moduleItemMapper (MIPackageItem (Import x y)) =
|
||||
return $ MIPackageItem $ Import x y
|
||||
moduleItemMapper (AssertionItem (mx, a)) = do
|
||||
a' <- traverseAssertionStmtsM stmtMapper a
|
||||
a'' <- traverseAssertionExprsM exprMapper a'
|
||||
|
|
@ -792,6 +792,8 @@ traverseTypesM mapper item =
|
|||
fullMapper t >>= \t' -> return $ Localparam t' x e
|
||||
declMapper (Variable d t x a me) =
|
||||
fullMapper t >>= \t' -> return $ Variable d t' x a me
|
||||
miMapper (MIPackageItem (Typedef t x)) =
|
||||
fullMapper t >>= \t' -> return $ MIPackageItem $ Typedef t' x
|
||||
miMapper (MIPackageItem (Function l t x d s)) =
|
||||
fullMapper t >>= \t' -> return $ MIPackageItem $ Function l t' x d s
|
||||
miMapper (MIPackageItem (other @ (Task _ _ _ _))) =
|
||||
|
|
|
|||
|
|
@ -17,8 +17,11 @@ import Language.SystemVerilog.AST
|
|||
|
||||
type Types = Map.Map Identifier Type
|
||||
|
||||
convert :: AST -> AST
|
||||
convert descriptions =
|
||||
convert :: [AST] -> [AST]
|
||||
convert = map convertFile
|
||||
|
||||
convertFile :: AST -> AST
|
||||
convertFile descriptions =
|
||||
traverseDescriptions removeTypedef $
|
||||
traverseDescriptions (convertDescription types) $
|
||||
descriptions
|
||||
|
|
|
|||
|
|
@ -13,8 +13,9 @@ module Convert.UnbasedUnsized (convert) where
|
|||
import Convert.Traverse
|
||||
import Language.SystemVerilog.AST
|
||||
|
||||
convert :: AST -> AST
|
||||
convert :: [AST] -> [AST]
|
||||
convert =
|
||||
map $
|
||||
traverseDescriptions $ traverseModuleItems $
|
||||
traverseExprs $ traverseNestedExprs convertExpr
|
||||
|
||||
|
|
|
|||
|
|
@ -13,8 +13,9 @@ module Convert.Unique (convert) where
|
|||
import Convert.Traverse
|
||||
import Language.SystemVerilog.AST
|
||||
|
||||
convert :: AST -> AST
|
||||
convert = traverseDescriptions $ traverseModuleItems $ traverseStmts convertStmt
|
||||
convert :: [AST] -> [AST]
|
||||
convert =
|
||||
map $ traverseDescriptions $ traverseModuleItems $ traverseStmts convertStmt
|
||||
|
||||
convertStmt :: Stmt -> Stmt
|
||||
convertStmt (If (Just _) cc s1 s2) =
|
||||
|
|
|
|||
|
|
@ -56,7 +56,7 @@ data PackageItem
|
|||
= Typedef Type Identifier
|
||||
| Function (Maybe Lifetime) Type Identifier [Decl] [Stmt]
|
||||
| Task (Maybe Lifetime) Identifier [Decl] [Stmt]
|
||||
| Import [(Identifier, Maybe Identifier)]
|
||||
| Import Identifier (Maybe Identifier)
|
||||
| Decl Decl
|
||||
| Comment String
|
||||
deriving Eq
|
||||
|
|
@ -71,11 +71,7 @@ instance Show PackageItem where
|
|||
printf "task %s%s;\n%s\n%s\nendtask"
|
||||
(showLifetime ml) x (indent $ show i)
|
||||
(indent $ unlines' $ map show b)
|
||||
show (Import imports) =
|
||||
printf "import %s;"
|
||||
(commas $ map showImport imports)
|
||||
where
|
||||
showImport (x, y) = printf "%s::%s" x (fromMaybe "*" y)
|
||||
show (Import x y) = printf "import %s::%s;" x (fromMaybe "*" y)
|
||||
show (Decl decl) = show decl
|
||||
show (Comment c) =
|
||||
if elem '\n' c
|
||||
|
|
|
|||
|
|
@ -454,7 +454,7 @@ NonGenerateModuleItem :: { [ModuleItem] }
|
|||
| "initial" Stmt { [Initial $2] }
|
||||
| "genvar" Identifiers ";" { map Genvar $2 }
|
||||
| "modport" ModportItems ";" { map (uncurry Modport) $2 }
|
||||
| NonDeclPackageItem { [MIPackageItem $1] }
|
||||
| NonDeclPackageItem { map MIPackageItem $1 }
|
||||
| NInputGateKW NInputGates ";" { map (\(a, b, c) -> NInputGate $1 a b c) $2 }
|
||||
| NOutputGateKW NOutputGates ";" { map (\(a, b, c) -> NOutputGate $1 a b c) $2 }
|
||||
| AttributeInstance ModuleItem { map (MIAttr $1) $2 }
|
||||
|
|
@ -570,12 +570,12 @@ PackageItems :: { [PackageItem] }
|
|||
PackageItem :: { [PackageItem] }
|
||||
: DeclTokens(";") { map Decl $ parseDTsAsDecls $1 }
|
||||
| ParameterDecl(ParameterDeclKW, ";") { map Decl $1 }
|
||||
| NonDeclPackageItem { [$1] }
|
||||
NonDeclPackageItem :: { PackageItem }
|
||||
: "typedef" Type Identifier ";" { Typedef $2 $3 }
|
||||
| "function" opt(Lifetime) FuncRetAndName TFItems DeclsAndStmts "endfunction" opt(Tag) { Function $2 (fst $3) (snd $3) (map defaultFuncInput $ (map makeInput $4) ++ fst $5) (snd $5) }
|
||||
| "task" opt(Lifetime) Identifier TFItems DeclsAndStmts "endtask" opt(Tag) { Task $2 $3 (map defaultFuncInput $ $4 ++ fst $5) (snd $5) }
|
||||
| "import" PackageImportItems ";" { Import $2 }
|
||||
| NonDeclPackageItem { $1 }
|
||||
NonDeclPackageItem :: { [PackageItem] }
|
||||
: "typedef" Type Identifier ";" { [Typedef $2 $3] }
|
||||
| "function" opt(Lifetime) FuncRetAndName TFItems DeclsAndStmts "endfunction" opt(Tag) { [Function $2 (fst $3) (snd $3) (map defaultFuncInput $ (map makeInput $4) ++ fst $5) (snd $5)] }
|
||||
| "task" opt(Lifetime) Identifier TFItems DeclsAndStmts "endtask" opt(Tag) { [Task $2 $3 (map defaultFuncInput $ $4 ++ fst $5) (snd $5)] }
|
||||
| "import" PackageImportItems ";" { map (uncurry Import) $2 }
|
||||
|
||||
PackageImportItems :: { [(Identifier, Maybe Identifier)] }
|
||||
: PackageImportItem { [$1] }
|
||||
|
|
|
|||
|
|
@ -25,9 +25,8 @@ main = do
|
|||
let includePaths = incdir job
|
||||
let defines = map splitDefine $ define job
|
||||
asts <- mapM (parseFile includePaths defines) (files job)
|
||||
let ast = concat asts
|
||||
-- convert the file
|
||||
let ast' = convert (exclude job) ast
|
||||
let asts' = convert (exclude job) asts
|
||||
-- print the converted file out
|
||||
hPrint stdout ast'
|
||||
hPrint stdout $ concat asts'
|
||||
exitSuccess
|
||||
|
|
|
|||
|
|
@ -63,7 +63,7 @@ executable sv2v
|
|||
Convert.KWArgs
|
||||
Convert.Logic
|
||||
Convert.NamedBlock
|
||||
Convert.NestTF
|
||||
Convert.NestPI
|
||||
Convert.PackedArray
|
||||
Convert.Return
|
||||
Convert.StarPort
|
||||
|
|
|
|||
|
|
@ -9,7 +9,9 @@ function baz;
|
|||
input [2:0] n;
|
||||
baz = n * 2;
|
||||
endfunction
|
||||
localparam PARAM = 37;
|
||||
module top;
|
||||
initial foo();
|
||||
initial $display("bar(0) = %d", bar(0));
|
||||
initial $display("PARAM = %d", PARAM);
|
||||
endmodule
|
||||
|
|
|
|||
|
|
@ -10,6 +10,8 @@ module top;
|
|||
input [2:0] n;
|
||||
baz = n * 2;
|
||||
endfunction
|
||||
localparam PARAM = 37;
|
||||
initial foo();
|
||||
initial $display("bar(0) = %d", bar(0));
|
||||
initial $display("PARAM = %d", PARAM);
|
||||
endmodule
|
||||
|
|
|
|||
Loading…
Reference in New Issue