mirror of https://github.com/zachjs/sv2v.git
improved handling of string parameters
- variable-size string parameter conversion restricted to modules which depend on the size of the string parameter - string localparams are typed as appropriately sized vectors - remove ordered parameter binding logic from string param conversion
This commit is contained in:
parent
280d3dc5a6
commit
7ffea36ddd
|
|
@ -1,18 +1,27 @@
|
|||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-
|
||||
- Conversion for variable-length string parameters
|
||||
-
|
||||
- While implicitly variable-length string parameters are supported in
|
||||
- Verilog-2005, some usages depend on their type information (e.g., size). In
|
||||
- such instances, an additional parameter is added encoding the width of the
|
||||
- parameter.
|
||||
-}
|
||||
|
||||
module Convert.StringParam (convert) where
|
||||
|
||||
import Control.Monad.Writer.Strict
|
||||
import Data.Maybe (mapMaybe)
|
||||
import qualified Data.Set as Set
|
||||
import qualified Data.Map.Strict as Map
|
||||
|
||||
import Convert.Traverse
|
||||
import Language.SystemVerilog.AST
|
||||
|
||||
type PartStringParams = Map.Map Identifier [(Identifier, Int)]
|
||||
type PartStringParams = Map.Map Identifier [Identifier]
|
||||
type Idents = Set.Set Identifier
|
||||
|
||||
convert :: [AST] -> [AST]
|
||||
convert files =
|
||||
|
|
@ -28,67 +37,70 @@ convert files =
|
|||
-- adds automatic width parameters for string parameters
|
||||
traverseDescriptionM :: Description -> Writer PartStringParams Description
|
||||
traverseDescriptionM (Part attrs extern kw lifetime name ports items) =
|
||||
if null stringParamNames
|
||||
if null candidateStringParams || Set.null stringParamNames
|
||||
then return $ Part attrs extern kw lifetime name ports items
|
||||
else do
|
||||
tell $ Map.singleton name stringParamIds
|
||||
tell $ Map.singleton name $ Set.toList stringParamNames
|
||||
return $ Part attrs extern kw lifetime name ports items'
|
||||
where
|
||||
(items', stringParamNames) = runWriter $
|
||||
mapM (traverseNestedModuleItemsM traverseModuleItemM) items
|
||||
allParamNames = parameterNames items
|
||||
stringParamIds = filter (flip elem stringParamNames . fst) $
|
||||
zip allParamNames [0..]
|
||||
items' = map (elaborateStringParam stringParamNames) items
|
||||
candidateStringParams = mapMaybe candidateStringParam items
|
||||
stringParamNames = execWriter $
|
||||
mapM (collectNestedModuleItemsM collectModuleItemM) items
|
||||
collectModuleItemM = collectTypesM $ collectNestedTypesM $
|
||||
collectQueriedIdentsM $ Set.fromList candidateStringParams
|
||||
traverseDescriptionM other = return other
|
||||
|
||||
-- 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] ()
|
||||
collectDeclM (Param Parameter _ x _) = tell [x]
|
||||
collectDeclM (ParamType Parameter x _) = tell [x]
|
||||
collectDeclM _ = return ()
|
||||
-- utility pattern for candidate string parameter items
|
||||
pattern StringParam :: Identifier -> String -> ModuleItem
|
||||
pattern StringParam x s =
|
||||
MIPackageItem (Decl (Param Parameter UnknownType x (String s)))
|
||||
|
||||
-- write down which parameters may be variable-length strings
|
||||
candidateStringParam :: ModuleItem -> Maybe Identifier
|
||||
candidateStringParam (MIAttr _ item) = candidateStringParam item
|
||||
candidateStringParam (StringParam x _) = Just x
|
||||
candidateStringParam _ = Nothing
|
||||
|
||||
-- write down which of the given identifiers are subject to type queries
|
||||
collectQueriedIdentsM :: Idents -> Type -> Writer Idents ()
|
||||
collectQueriedIdentsM idents (TypeOf (Ident x)) =
|
||||
when (Set.member x idents) $ tell $ Set.singleton x
|
||||
collectQueriedIdentsM _ _ = return ()
|
||||
|
||||
-- rewrite an existing string parameter
|
||||
traverseModuleItemM :: ModuleItem -> Writer [Identifier] ModuleItem
|
||||
traverseModuleItemM (orig @ (MIPackageItem (Decl (Param Parameter t x e)))) =
|
||||
case (t, e) of
|
||||
(UnknownType, String str) -> do
|
||||
tell [x]
|
||||
return $ Generate $ map wrap [width str, param str]
|
||||
where wrap = GenModuleItem . MIPackageItem . Decl
|
||||
_ -> return orig
|
||||
elaborateStringParam :: Idents -> ModuleItem -> ModuleItem
|
||||
elaborateStringParam idents (MIAttr attr item) =
|
||||
MIAttr attr $ elaborateStringParam idents item
|
||||
elaborateStringParam idents (orig @ (StringParam x str)) =
|
||||
if Set.member x idents
|
||||
then Generate $ map wrap [width, param]
|
||||
else orig
|
||||
where
|
||||
wrap = GenModuleItem . MIPackageItem . Decl
|
||||
w = widthName x
|
||||
r = (BinOp Sub (Ident w) (RawNum 1), RawNum 0)
|
||||
t' = IntegerVector TBit Unspecified [r]
|
||||
defaultWidth str = DimsFn FnBits $ Right $ String str
|
||||
width str = Param Parameter UnknownType w (defaultWidth str)
|
||||
param str = Param Parameter t' x (String str)
|
||||
traverseModuleItemM other = return other
|
||||
defaultWidth = DimsFn FnBits $ Right $ String str
|
||||
width = Param Parameter UnknownType w defaultWidth
|
||||
param = Param Parameter t' x (String str)
|
||||
elaborateStringParam _ other = other
|
||||
|
||||
widthName :: Identifier -> Identifier
|
||||
widthName paramName = "_sv2v_width_" ++ paramName
|
||||
|
||||
-- convert isntances which use the converted string parameters
|
||||
-- convert instances which use the converted string parameters
|
||||
mapInstance :: PartStringParams -> ModuleItem -> ModuleItem
|
||||
mapInstance partStringParams (Instance m params x rs ports) =
|
||||
case Map.lookup m partStringParams of
|
||||
Nothing -> Instance m params x rs ports
|
||||
Just stringParams -> Instance m params' x rs ports
|
||||
where params' = concat $ zipWith (expand stringParams) params [0..]
|
||||
where params' = concatMap (expand stringParams) params
|
||||
where
|
||||
expand :: [(Identifier, Int)] -> ParamBinding -> Int -> [ParamBinding]
|
||||
expand _ (paramName, Left t) _ = [(paramName, Left t)]
|
||||
expand stringParams (orig @ ("", Right expr)) idx =
|
||||
if elem idx $ map snd stringParams
|
||||
then [("", Right width), orig]
|
||||
else [orig]
|
||||
where width = DimsFn FnBits $ Right expr
|
||||
expand stringParams (orig @ (paramName, Right expr)) _ =
|
||||
if elem paramName $ map fst stringParams
|
||||
expand :: [Identifier] -> ParamBinding -> [ParamBinding]
|
||||
expand _ (paramName, Left t) = [(paramName, Left t)]
|
||||
expand stringParams (orig @ (paramName, Right expr)) =
|
||||
if elem paramName stringParams
|
||||
then [(widthName paramName, Right width), orig]
|
||||
else [orig]
|
||||
where width = DimsFn FnBits $ Right expr
|
||||
|
|
|
|||
|
|
@ -56,8 +56,8 @@ traverseDeclM decl = do
|
|||
return $ case t' of
|
||||
UnpackedType t'' a' -> Variable d t'' ident a' e
|
||||
_ -> Variable d t' ident [] e
|
||||
Param _ UnknownType ident String{} ->
|
||||
insertType ident UnknownType >> return decl'
|
||||
Param Parameter UnknownType ident String{} ->
|
||||
insertType ident (TypeOf $ Ident ident) >> return decl'
|
||||
Param _ UnknownType ident e ->
|
||||
typeof e >>= insertType ident >> return decl'
|
||||
Param _ (Implicit sg rs) ident _ ->
|
||||
|
|
|
|||
|
|
@ -1,6 +1,6 @@
|
|||
module top;
|
||||
localparam FOO = "some useful string";
|
||||
localparam type T = type(FOO);
|
||||
localparam T BAR = "some other useful string";
|
||||
localparam T BAR = "some other useful string"; // clipped
|
||||
initial $display("'%s' '%s'", FOO, BAR);
|
||||
endmodule
|
||||
|
|
|
|||
|
|
@ -1,5 +1,6 @@
|
|||
module top;
|
||||
localparam FOO = "some useful string";
|
||||
localparam BAR = "some other useful string";
|
||||
localparam WIDTH = $bits("some useful string");
|
||||
localparam [WIDTH-1:0] BAR = "some other useful string"; // clipped
|
||||
initial $display("'%s' '%s'", FOO, BAR);
|
||||
endmodule
|
||||
|
|
|
|||
|
|
@ -0,0 +1,10 @@
|
|||
module other;
|
||||
parameter STR = "missing";
|
||||
initial $display("other: STR=%s $bits(STR)=%0d", STR, $bits(STR));
|
||||
endmodule
|
||||
|
||||
module mod;
|
||||
parameter STR = "missing";
|
||||
initial $display("mod: STR=%s", STR);
|
||||
other #("HI") m();
|
||||
endmodule
|
||||
|
|
@ -0,0 +1,4 @@
|
|||
module top;
|
||||
mod #("FOO") m1();
|
||||
mod #("BAR") m2();
|
||||
endmodule
|
||||
Loading…
Reference in New Issue