Commit 9fcc8e34 by Zachary Snow

enum generate localparam values are also explicitly sized to avoid implicit cast/warnings

parent a5ebb1e8
...@@ -27,7 +27,7 @@ import qualified Data.Set as Set ...@@ -27,7 +27,7 @@ import qualified Data.Set as Set
import Convert.Traverse import Convert.Traverse
import Language.SystemVerilog.AST import Language.SystemVerilog.AST
type EnumInfo = ([Range], [(Identifier, Maybe Expr)]) type EnumInfo = (Range, [(Identifier, Maybe Expr)])
type Enums = Set.Set EnumInfo type Enums = Set.Set EnumInfo
convert :: AST -> AST convert :: AST -> AST
...@@ -47,9 +47,12 @@ convertDescription (description @ (Part _ _ _ _ _ _)) = ...@@ -47,9 +47,12 @@ convertDescription (description @ (Part _ _ _ _ _ _)) =
traverseModuleItems (traverseExprs $ traverseNestedExprs traverseExpr) $ traverseModuleItems (traverseExprs $ traverseNestedExprs traverseExpr) $
description description
-- convert the collected enums into their corresponding localparams -- convert the collected enums into their corresponding localparams
itemType = Implicit Unspecified itemType r = Implicit Unspecified [r]
enumPairs = sortOn snd $ concatMap enumVals $ Set.toList enums enumPairs = sortOn snd $ concatMap enumVals $ Set.toList enums
enumItems = map (\((r, x), v) -> MIDecl $ Localparam (itemType r) x v) enumPairs enumItems = map toItem enumPairs
toItem ((r, x), v) =
MIDecl $ Localparam (itemType r) x v'
where v' = sizedExpr x r (simplify v)
convertDescription other = other convertDescription other = other
toBaseType :: Maybe Type -> Type toBaseType :: Maybe Type -> Type
...@@ -66,9 +69,9 @@ toBaseType (Just t) = ...@@ -66,9 +69,9 @@ toBaseType (Just t) =
traverseType :: Type -> Writer Enums Type traverseType :: Type -> Writer Enums Type
traverseType (Enum t v rs) = do traverseType (Enum t v rs) = do
let baseType = toBaseType t let baseType = toBaseType t
let (tf, r) = typeRanges baseType let (tf, [r]) = typeRanges baseType
() <- tell $ Set.singleton (map simplifyRange r, v) () <- tell $ Set.singleton (simplifyRange r, v)
return $ tf (r ++ rs) return $ tf (r : rs)
traverseType other = return other traverseType other = return other
simplifyRange :: Range -> Range simplifyRange :: Range -> Range
...@@ -80,7 +83,7 @@ traverseExpr :: Expr -> Expr ...@@ -80,7 +83,7 @@ traverseExpr :: Expr -> Expr
traverseExpr (Cast (Left (Enum _ _ _)) e) = e traverseExpr (Cast (Left (Enum _ _ _)) e) = e
traverseExpr other = other traverseExpr other = other
enumVals :: ([Range], [(Identifier, Maybe Expr)]) -> [(([Range], Identifier), Expr)] enumVals :: (Range, [(Identifier, Maybe Expr)]) -> [((Range, Identifier), Expr)]
enumVals (r, l) = enumVals (r, l) =
-- check for obviously duplicate values -- check for obviously duplicate values
if noDuplicates if noDuplicates
......
...@@ -10,7 +10,6 @@ import Data.Maybe (fromJust, isJust) ...@@ -10,7 +10,6 @@ import Data.Maybe (fromJust, isJust)
import Data.List (elemIndex, sortOn) import Data.List (elemIndex, sortOn)
import Data.Tuple (swap) import Data.Tuple (swap)
import Control.Monad.Writer import Control.Monad.Writer
import Text.Read (readMaybe)
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
import Convert.Traverse import Convert.Traverse
...@@ -253,23 +252,8 @@ convertAsgn structs types (lhs, expr) = ...@@ -253,23 +252,8 @@ convertAsgn structs types (lhs, expr) =
fieldNames = map snd fields fieldNames = map snd fields
itemsFieldNames = map (fromJust . fst) items itemsFieldNames = map (fromJust . fst) items
itemPosition = \(Just x, _) -> fromJust $ elemIndex x fieldNames itemPosition = \(Just x, _) -> fromJust $ elemIndex x fieldNames
packItem (Just x, Number n) = packItem (Just x, e) = sizedExpr x r e
if size /= show resSize where r = lookupUnstructRange structTf x
then error $ "literal " ++ show n ++ " for " ++ show x
++ " doesn't have struct field size " ++ show size
else Number res
where
Number size = rangeSize $ lookupUnstructRange structTf x
unticked = case n of
'\'' : rest -> rest
rest -> rest
resSize = (read $ takeWhile (/= '\'') res) :: Int
res = case readMaybe unticked :: Maybe Int of
Nothing ->
if unticked == n
then n
else size ++ n
Just num -> size ++ "'d" ++ show num
packItem (_, itemExpr) = itemExpr packItem (_, itemExpr) = itemExpr
convertExpr _ other = other convertExpr _ other = other
......
...@@ -16,6 +16,7 @@ module Language.SystemVerilog.AST.Expr ...@@ -16,6 +16,7 @@ module Language.SystemVerilog.AST.Expr
, rangeSize , rangeSize
, endianCondExpr , endianCondExpr
, endianCondRange , endianCondRange
, sizedExpr
) where ) where
import Data.List (intercalate) import Data.List (intercalate)
...@@ -187,3 +188,24 @@ endianCondRange r r1 r2 = ...@@ -187,3 +188,24 @@ endianCondRange r r1 r2 =
( endianCondExpr r (fst r1) (fst r2) ( endianCondExpr r (fst r1) (fst r2)
, endianCondExpr r (snd r1) (snd r2) , endianCondExpr r (snd r1) (snd r2)
) )
-- attempts to make a number literal have an explicit size
sizedExpr :: Identifier -> Range -> Expr -> Expr
sizedExpr x r (Number n) =
if size /= show resSize
then error $ "literal " ++ show n ++ " for " ++ show x
++ " doesn't have size " ++ show size
else Number res
where
Number size = simplify $ rangeSize r
unticked = case n of
'\'' : rest -> rest
rest -> rest
resSize = (read $ takeWhile (/= '\'') res) :: Int
res = case readMaybe unticked :: Maybe Int of
Nothing ->
if unticked == n
then n
else size ++ n
Just num -> size ++ "'d" ++ show num
sizedExpr _ _ e = 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