Commit 92feef87 by Zachary Snow

standardized, shorter hash generation

parent 9435c9d9
...@@ -70,10 +70,7 @@ streamerBlock chunk size asgn output input = ...@@ -70,10 +70,7 @@ streamerBlock chunk size asgn output input =
streamerBlockName :: Expr -> Expr -> Identifier streamerBlockName :: Expr -> Expr -> Identifier
streamerBlockName chunk size = streamerBlockName chunk size =
"_sv2v_strm_" ++ take 5 str "_sv2v_strm_" ++ shortHash (chunk, size)
where
val = hash $ show (chunk, size)
str = tail $ show val
traverseStmtM :: Stmt -> Writer Funcs Stmt traverseStmtM :: Stmt -> Writer Funcs Stmt
traverseStmtM (AsgnBlk op lhs expr) = traverseStmtM (AsgnBlk op lhs expr) =
......
...@@ -8,7 +8,6 @@ module Convert.Struct (convert) where ...@@ -8,7 +8,6 @@ module Convert.Struct (convert) where
import Control.Monad.State import Control.Monad.State
import Control.Monad.Writer import Control.Monad.Writer
import Data.Hashable (hash)
import Data.List (elemIndex, sortOn) import Data.List (elemIndex, sortOn)
import Data.Maybe (fromJust, isJust) import Data.Maybe (fromJust, isJust)
import Data.Tuple (swap) import Data.Tuple (swap)
...@@ -207,10 +206,7 @@ packerFn structTf = ...@@ -207,10 +206,7 @@ packerFn structTf =
-- returns a "unique" name for the packer for a given struct type -- returns a "unique" name for the packer for a given struct type
packerFnName :: TypeFunc -> Identifier packerFnName :: TypeFunc -> Identifier
packerFnName structTf = packerFnName structTf =
"sv2v_pack_struct_" ++ str "sv2v_struct_" ++ shortHash structTf
where
val = hash $ show structTf
str = tail $ show val
-- This is where the magic happens. This is responsible for converting struct -- This is where the magic happens. This is responsible for converting struct
-- accesses, assignments, and literals, given appropriate information about the -- accesses, assignments, and literals, given appropriate information about the
......
...@@ -27,8 +27,12 @@ module Language.SystemVerilog.AST ...@@ -27,8 +27,12 @@ module Language.SystemVerilog.AST
, module Type , module Type
, exprToLHS , exprToLHS
, lhsToExpr , lhsToExpr
, shortHash
) where ) where
import Text.Printf (printf)
import Data.Hashable (hash)
import Language.SystemVerilog.AST.Attr as Attr import Language.SystemVerilog.AST.Attr as Attr
import Language.SystemVerilog.AST.Decl as Decl import Language.SystemVerilog.AST.Decl as Decl
import Language.SystemVerilog.AST.Description as Description import Language.SystemVerilog.AST.Description as Description
...@@ -68,3 +72,8 @@ lhsToExpr (LHSRange l m r ) = Range (lhsToExpr l) m r ...@@ -68,3 +72,8 @@ lhsToExpr (LHSRange l m r ) = Range (lhsToExpr l) m r
lhsToExpr (LHSDot l x ) = Dot (lhsToExpr l) x lhsToExpr (LHSDot l x ) = Dot (lhsToExpr l) x
lhsToExpr (LHSConcat ls) = Concat $ map lhsToExpr ls lhsToExpr (LHSConcat ls) = Concat $ map lhsToExpr ls
lhsToExpr (LHSStream o e ls) = Stream o e $ map lhsToExpr ls lhsToExpr (LHSStream o e ls) = Stream o e $ map lhsToExpr ls
shortHash :: (Show a) => a -> String
shortHash x =
take 5 $ printf "%05X" val
where val = hash $ show x
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