Commit 11dbf1a4 by Zachary Snow

remove dead code in ubased unsized conversion

parent 18358063
...@@ -18,20 +18,19 @@ ...@@ -18,20 +18,19 @@
module Convert.UnbasedUnsized (convert) where module Convert.UnbasedUnsized (convert) where
import Control.Monad.Writer.Strict import Control.Monad.Writer.Strict
import Data.Maybe (catMaybes) import Data.Maybe (mapMaybe)
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
import Convert.ExprUtils import Convert.ExprUtils
import Convert.Traverse import Convert.Traverse
import Language.SystemVerilog.AST import Language.SystemVerilog.AST
type Part = ([Identifier], [ModuleItem]) type Part = [ModuleItem]
type Parts = Map.Map Identifier Part type Parts = Map.Map Identifier Part
data ExprContext data ExprContext
= SelfDetermined = SelfDetermined
| ContextDetermined Expr | ContextDetermined Expr
deriving (Eq, Show)
convert :: [AST] -> [AST] convert :: [AST] -> [AST]
convert files = convert files =
...@@ -41,8 +40,8 @@ convert files = ...@@ -41,8 +40,8 @@ convert files =
convertDescription = traverseModuleItems $ convertModuleItem parts convertDescription = traverseModuleItems $ convertModuleItem parts
collectPartsM :: Description -> Writer Parts () collectPartsM :: Description -> Writer Parts ()
collectPartsM (Part _ _ _ _ name ports items) = collectPartsM (Part _ _ _ _ name _ items) =
tell $ Map.singleton name (ports, items) tell $ Map.singleton name items
collectPartsM _ = return () collectPartsM _ = return ()
convertModuleItem :: Parts -> ModuleItem -> ModuleItem convertModuleItem :: Parts -> ModuleItem -> ModuleItem
...@@ -52,8 +51,8 @@ convertModuleItem parts (Instance moduleName params instanceName [] bindings) = ...@@ -52,8 +51,8 @@ convertModuleItem parts (Instance moduleName params instanceName [] bindings) =
Instance moduleName params instanceName [] bindings' Instance moduleName params instanceName [] bindings'
else Instance moduleName params instanceName [] bindings else Instance moduleName params instanceName [] bindings
where where
bindings' = zipWith convertBinding bindings [0..] bindings' = map convertBinding bindings
(portNames, moduleItems) = moduleItems =
case Map.lookup moduleName parts of case Map.lookup moduleName parts of
Nothing -> error $ "could not find module: " ++ moduleName Nothing -> error $ "could not find module: " ++ moduleName
Just partInfo -> partInfo Just partInfo -> partInfo
...@@ -61,40 +60,30 @@ convertModuleItem parts (Instance moduleName params instanceName [] bindings) = ...@@ -61,40 +60,30 @@ convertModuleItem parts (Instance moduleName params instanceName [] bindings) =
isTypeParam (MIPackageItem (Decl ParamType{})) = True isTypeParam (MIPackageItem (Decl ParamType{})) = True
isTypeParam _ = False isTypeParam _ = False
tag = Ident "~~uub~~" tag = Ident "~~uub~~"
convertBinding :: PortBinding -> Int -> PortBinding convertBinding :: PortBinding -> PortBinding
convertBinding (portName, expr) idx = convertBinding (portName, expr) =
(portName, ) $ (portName, ) $
traverseNestedExprs (replaceBindingExpr portName idx) $ traverseNestedExprs (replaceBindingExpr portName) $
convertExpr (ContextDetermined tag) expr convertExpr (ContextDetermined tag) expr
replaceBindingExpr :: Identifier -> Int -> Expr -> Expr replaceBindingExpr :: Identifier -> Expr -> Expr
replaceBindingExpr portName idx (orig @ (Repeat _ [ConvertedUU a b])) = replaceBindingExpr portName (orig @ (Repeat _ [ConvertedUU a b])) =
if orig == sizedLiteralFor tag bit if orig == sizedLiteralFor tag bit
then Repeat portSize [ConvertedUU a b] then Repeat portSize [ConvertedUU a b]
else orig else orig
where where
bit = bitForBased a b bit = bitForBased a b
portName' = portSize = determinePortSize portName params moduleItems
if null portName replaceBindingExpr _ other = other
then lookupBindingName portNames idx
else portName
portSize = determinePortSize portName' params moduleItems
replaceBindingExpr _ _ other = other
convertModuleItem _ other = convertModuleItem' other convertModuleItem _ other = convertModuleItem' other
determinePortSize :: Identifier -> [ParamBinding] -> [ModuleItem] -> Expr determinePortSize :: Identifier -> [ParamBinding] -> [ModuleItem] -> Expr
determinePortSize portName instanceParams moduleItems = determinePortSize portName instanceParams moduleItems =
step (reverse initialMapping) moduleItems step (reverse initialMapping) moduleItems
where where
moduleParams = parameterNames moduleItems initialMapping = mapMaybe createParamReplacement instanceParams
initialMapping = catMaybes $ createParamReplacement :: ParamBinding -> Maybe (Identifier, Expr)
zipWith createParamReplacement instanceParams [0..] createParamReplacement (_, Left _) = Nothing
createParamReplacement createParamReplacement (paramName, Right expr) =
:: ParamBinding -> Int -> Maybe (Identifier, Expr)
createParamReplacement ("", b) idx =
createParamReplacement (paramName, b) idx
where paramName = lookupBindingName moduleParams idx
createParamReplacement (_, Left _) _ = Nothing
createParamReplacement (paramName, Right expr) _ =
Just (paramName, tagExpr expr) Just (paramName, tagExpr expr)
step :: [(Identifier, Expr)] -> [ModuleItem] -> Expr step :: [(Identifier, Expr)] -> [ModuleItem] -> Expr
...@@ -137,22 +126,6 @@ tagExpr :: Expr -> Expr ...@@ -137,22 +126,6 @@ tagExpr :: Expr -> Expr
tagExpr (Ident x) = Ident (':' : x) tagExpr (Ident x) = Ident (':' : x)
tagExpr expr = traverseSinglyNestedExprs tagExpr expr tagExpr expr = traverseSinglyNestedExprs tagExpr expr
-- 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 ()
lookupBindingName :: [Identifier] -> Int -> Identifier
lookupBindingName names idx =
if idx < length names
then names !! idx
else error $ "out of bounds binding " ++ show (names, idx)
convertModuleItem' :: ModuleItem -> ModuleItem convertModuleItem' :: ModuleItem -> ModuleItem
convertModuleItem' = convertModuleItem' =
traverseExprs (convertExpr SelfDetermined) . traverseExprs (convertExpr SelfDetermined) .
...@@ -251,7 +224,7 @@ convertExpr (ContextDetermined expr) (UU bit) = ...@@ -251,7 +224,7 @@ convertExpr (ContextDetermined expr) (UU bit) =
convertExpr _ other = other convertExpr _ other = other
pattern UU :: Bit -> Expr pattern UU :: Bit -> Expr
pattern UU bit = Number (UnbasedUnsized bit) pattern UU bit <- Number (UnbasedUnsized bit)
convertType :: Type -> Type convertType :: Type -> Type
convertType (TypeOf e) = TypeOf $ convertExpr SelfDetermined e convertType (TypeOf e) = TypeOf $ convertExpr SelfDetermined e
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment