Commit bf029068 by Zachary Snow

move exprToType utility outside to language module

parent 9acdb848
......@@ -31,7 +31,7 @@ import Data.Maybe (mapMaybe)
import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
import Convert.ResolveBindings (exprToType, resolveBindings)
import Convert.ResolveBindings (resolveBindings)
import Convert.Scoper
import Convert.Traverse
import Language.SystemVerilog.AST
......
......@@ -12,7 +12,6 @@
module Convert.ResolveBindings
( convert
, exprToType
, resolveBindings
) where
......@@ -20,7 +19,6 @@ import Control.Monad.Writer.Strict
import Data.List (intercalate, (\\))
import qualified Data.Map.Strict as Map
import Convert.ExprUtils (simplify)
import Convert.Traverse
import Language.SystemVerilog.AST
......@@ -100,20 +98,6 @@ mapInstance parts (Instance m paramBindings x rs portBindings) =
mapInstance _ other = other
-- attempt to convert an expression to syntactically equivalent type
exprToType :: Expr -> Maybe Type
exprToType (Ident x) = Just $ Alias x []
exprToType (PSIdent y x) = Just $ PSAlias y x []
exprToType (CSIdent y p x) = Just $ CSAlias y p x []
exprToType (Range e NonIndexed r) = do
(tf, rs) <- fmap typeRanges $ exprToType e
Just $ tf (rs ++ [r])
exprToType (Bit e i) = do
(tf, rs) <- fmap typeRanges $ exprToType e
let r = (simplify $ BinOp Sub i (RawNum 1), RawNum 0)
Just $ tf (rs ++ [r])
exprToType _ = Nothing
type Binding t = (Identifier, t)
-- give a set of bindings explicit names
resolveBindings :: String -> [Identifier] -> [Binding t] -> [Binding t]
......
......@@ -28,6 +28,7 @@ module Language.SystemVerilog.AST
, module Type
, exprToLHS
, lhsToExpr
, exprToType
, shortHash
) where
......@@ -81,6 +82,20 @@ lhsToExpr (LHSDot l x ) = Dot (lhsToExpr l) x
lhsToExpr (LHSConcat ls) = Concat $ map lhsToExpr ls
lhsToExpr (LHSStream o e ls) = Stream o e $ map lhsToExpr ls
-- attempt to convert an expression to a syntactically equivalent type
exprToType :: Expr -> Maybe Type
exprToType (Ident x) = Just $ Alias x []
exprToType (PSIdent y x) = Just $ PSAlias y x []
exprToType (CSIdent y p x) = Just $ CSAlias y p x []
exprToType (Range e NonIndexed r) = do
(tf, rs) <- fmap typeRanges $ exprToType e
Just $ tf (rs ++ [r])
exprToType (Bit e i) = do
(tf, rs) <- fmap typeRanges $ exprToType e
let r = (BinOp Sub i (RawNum 1), RawNum 0)
Just $ tf (rs ++ [r])
exprToType _ = Nothing
shortHash :: (Show a) => a -> String
shortHash x =
printf "%05X" $ val .&. 0xFFFFF
......
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