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
|
{- sv2v
|
||||||
- Author: Zachary Snow <zach@zachjs.com>
|
- Author: Zachary Snow <zach@zachjs.com>
|
||||||
-
|
-
|
||||||
- Conversion for variable-length string parameters
|
- 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
|
module Convert.StringParam (convert) where
|
||||||
|
|
||||||
import Control.Monad.Writer.Strict
|
import Control.Monad.Writer.Strict
|
||||||
|
import Data.Maybe (mapMaybe)
|
||||||
|
import qualified Data.Set as Set
|
||||||
import qualified Data.Map.Strict as Map
|
import qualified Data.Map.Strict as Map
|
||||||
|
|
||||||
import Convert.Traverse
|
import Convert.Traverse
|
||||||
import Language.SystemVerilog.AST
|
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 :: [AST] -> [AST]
|
||||||
convert files =
|
convert files =
|
||||||
|
|
@ -28,67 +37,70 @@ convert files =
|
||||||
-- adds automatic width parameters for string parameters
|
-- adds automatic width parameters for string parameters
|
||||||
traverseDescriptionM :: Description -> Writer PartStringParams Description
|
traverseDescriptionM :: Description -> Writer PartStringParams Description
|
||||||
traverseDescriptionM (Part attrs extern kw lifetime name ports items) =
|
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
|
then return $ Part attrs extern kw lifetime name ports items
|
||||||
else do
|
else do
|
||||||
tell $ Map.singleton name stringParamIds
|
tell $ Map.singleton name $ Set.toList stringParamNames
|
||||||
return $ Part attrs extern kw lifetime name ports items'
|
return $ Part attrs extern kw lifetime name ports items'
|
||||||
where
|
where
|
||||||
(items', stringParamNames) = runWriter $
|
items' = map (elaborateStringParam stringParamNames) items
|
||||||
mapM (traverseNestedModuleItemsM traverseModuleItemM) items
|
candidateStringParams = mapMaybe candidateStringParam items
|
||||||
allParamNames = parameterNames items
|
stringParamNames = execWriter $
|
||||||
stringParamIds = filter (flip elem stringParamNames . fst) $
|
mapM (collectNestedModuleItemsM collectModuleItemM) items
|
||||||
zip allParamNames [0..]
|
collectModuleItemM = collectTypesM $ collectNestedTypesM $
|
||||||
|
collectQueriedIdentsM $ Set.fromList candidateStringParams
|
||||||
traverseDescriptionM other = return other
|
traverseDescriptionM other = return other
|
||||||
|
|
||||||
-- given a list of module items, produces the parameter names in order
|
-- utility pattern for candidate string parameter items
|
||||||
parameterNames :: [ModuleItem] -> [Identifier]
|
pattern StringParam :: Identifier -> String -> ModuleItem
|
||||||
parameterNames =
|
pattern StringParam x s =
|
||||||
execWriter . mapM (collectNestedModuleItemsM $ collectDeclsM collectDeclM)
|
MIPackageItem (Decl (Param Parameter UnknownType x (String s)))
|
||||||
where
|
|
||||||
collectDeclM :: Decl -> Writer [Identifier] ()
|
-- write down which parameters may be variable-length strings
|
||||||
collectDeclM (Param Parameter _ x _) = tell [x]
|
candidateStringParam :: ModuleItem -> Maybe Identifier
|
||||||
collectDeclM (ParamType Parameter x _) = tell [x]
|
candidateStringParam (MIAttr _ item) = candidateStringParam item
|
||||||
collectDeclM _ = return ()
|
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
|
-- rewrite an existing string parameter
|
||||||
traverseModuleItemM :: ModuleItem -> Writer [Identifier] ModuleItem
|
elaborateStringParam :: Idents -> ModuleItem -> ModuleItem
|
||||||
traverseModuleItemM (orig @ (MIPackageItem (Decl (Param Parameter t x e)))) =
|
elaborateStringParam idents (MIAttr attr item) =
|
||||||
case (t, e) of
|
MIAttr attr $ elaborateStringParam idents item
|
||||||
(UnknownType, String str) -> do
|
elaborateStringParam idents (orig @ (StringParam x str)) =
|
||||||
tell [x]
|
if Set.member x idents
|
||||||
return $ Generate $ map wrap [width str, param str]
|
then Generate $ map wrap [width, param]
|
||||||
where wrap = GenModuleItem . MIPackageItem . Decl
|
else orig
|
||||||
_ -> return orig
|
|
||||||
where
|
where
|
||||||
|
wrap = GenModuleItem . MIPackageItem . Decl
|
||||||
w = widthName x
|
w = widthName x
|
||||||
r = (BinOp Sub (Ident w) (RawNum 1), RawNum 0)
|
r = (BinOp Sub (Ident w) (RawNum 1), RawNum 0)
|
||||||
t' = IntegerVector TBit Unspecified [r]
|
t' = IntegerVector TBit Unspecified [r]
|
||||||
defaultWidth str = DimsFn FnBits $ Right $ String str
|
defaultWidth = DimsFn FnBits $ Right $ String str
|
||||||
width str = Param Parameter UnknownType w (defaultWidth str)
|
width = Param Parameter UnknownType w defaultWidth
|
||||||
param str = Param Parameter t' x (String str)
|
param = Param Parameter t' x (String str)
|
||||||
traverseModuleItemM other = return other
|
elaborateStringParam _ other = other
|
||||||
|
|
||||||
widthName :: Identifier -> Identifier
|
widthName :: Identifier -> Identifier
|
||||||
widthName paramName = "_sv2v_width_" ++ paramName
|
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 -> ModuleItem -> ModuleItem
|
||||||
mapInstance partStringParams (Instance m params x rs ports) =
|
mapInstance partStringParams (Instance m params x rs ports) =
|
||||||
case Map.lookup m partStringParams of
|
case Map.lookup m partStringParams of
|
||||||
Nothing -> Instance m params x rs ports
|
Nothing -> Instance m params x rs ports
|
||||||
Just stringParams -> 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
|
where
|
||||||
expand :: [(Identifier, Int)] -> ParamBinding -> Int -> [ParamBinding]
|
expand :: [Identifier] -> ParamBinding -> [ParamBinding]
|
||||||
expand _ (paramName, Left t) _ = [(paramName, Left t)]
|
expand _ (paramName, Left t) = [(paramName, Left t)]
|
||||||
expand stringParams (orig @ ("", Right expr)) idx =
|
expand stringParams (orig @ (paramName, Right expr)) =
|
||||||
if elem idx $ map snd stringParams
|
if elem paramName 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
|
|
||||||
then [(widthName paramName, Right width), orig]
|
then [(widthName paramName, Right width), orig]
|
||||||
else [orig]
|
else [orig]
|
||||||
where width = DimsFn FnBits $ Right expr
|
where width = DimsFn FnBits $ Right expr
|
||||||
|
|
|
||||||
|
|
@ -56,8 +56,8 @@ traverseDeclM decl = do
|
||||||
return $ case t' of
|
return $ case t' of
|
||||||
UnpackedType t'' a' -> Variable d t'' ident a' e
|
UnpackedType t'' a' -> Variable d t'' ident a' e
|
||||||
_ -> Variable d t' ident [] e
|
_ -> Variable d t' ident [] e
|
||||||
Param _ UnknownType ident String{} ->
|
Param Parameter UnknownType ident String{} ->
|
||||||
insertType ident UnknownType >> return decl'
|
insertType ident (TypeOf $ Ident ident) >> return decl'
|
||||||
Param _ UnknownType ident e ->
|
Param _ UnknownType ident e ->
|
||||||
typeof e >>= insertType ident >> return decl'
|
typeof e >>= insertType ident >> return decl'
|
||||||
Param _ (Implicit sg rs) ident _ ->
|
Param _ (Implicit sg rs) ident _ ->
|
||||||
|
|
|
||||||
|
|
@ -1,6 +1,6 @@
|
||||||
module top;
|
module top;
|
||||||
localparam FOO = "some useful string";
|
localparam FOO = "some useful string";
|
||||||
localparam type T = type(FOO);
|
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);
|
initial $display("'%s' '%s'", FOO, BAR);
|
||||||
endmodule
|
endmodule
|
||||||
|
|
|
||||||
|
|
@ -1,5 +1,6 @@
|
||||||
module top;
|
module top;
|
||||||
localparam FOO = "some useful string";
|
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);
|
initial $display("'%s' '%s'", FOO, BAR);
|
||||||
endmodule
|
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