Skip to content

Commit

Permalink
Dont prefix package name to types in _types package
Browse files Browse the repository at this point in the history
  • Loading branch information
christiaanb committed Aug 14, 2019
1 parent c9dc320 commit ece7f26
Showing 1 changed file with 32 additions and 21 deletions.
53 changes: 32 additions & 21 deletions clash-lib/src/Clash/Backend/SystemVerilog.hs
Original file line number Diff line number Diff line change
Expand Up @@ -85,6 +85,8 @@ data SystemVerilogState =
, _memoryDataFiles:: [(String,String)]
-- ^ Files to be stored: (filename, contents). These files are generated
-- during the execution of 'genNetlist'.
, _tyPkgCtx :: Bool
-- ^ Are we in the context of generating the @_types@ package?
, _intWidth :: Int -- ^ Int/Word/Integer bit-width
, _hdlsyn :: HdlSyn
, _escapedIds :: Bool
Expand All @@ -104,7 +106,9 @@ primsRoot = return ("clash-lib" System.FilePath.</> "prims")
#endif

instance Backend SystemVerilogState where
initBackend = SystemVerilogState HashSet.empty HashMapS.empty HashMap.empty 0 "" HashMapS.empty [] noSrcSpan [] [] [] [] []
initBackend = SystemVerilogState HashSet.empty HashMapS.empty HashMap.empty
0 "" HashMapS.empty [] noSrcSpan [] [] []
[] [] False
hdlKind = const SystemVerilog
primDirs = const $ do root <- primsRoot
return [ root System.FilePath.</> "common"
Expand Down Expand Up @@ -268,18 +272,21 @@ mkTyPackage_ :: Identifier
-> [HWType]
-> SystemVerilogM [(String,Doc)]
mkTyPackage_ modName hwtys = do
Mon (tyPkgCtx .= True)
normTys <- nub <$> mapM (normaliseType) (hwtys ++ usedTys)
let
needsDec = nubBy eqReprTy $ normTys
hwTysSorted = topSortHWTys needsDec
packageDec = vcat $ fmap catMaybes $ mapM tyDec hwTysSorted
funDecs = vcat $ fmap catMaybes $ mapM funDec hwTysSorted

(:[]) A.<$> (TextS.unpack modName ++ "_types",) A.<$>
pkg <- (:[]) A.<$> (TextS.unpack modName ++ "_types",) A.<$>
"package" <+> modNameD <> "_types" <> semi <> line <>
indent 2 packageDec <> line <>
indent 2 funDecs <> line <>
"endpackage" <+> colon <+> modNameD <> "_types"
Mon (tyPkgCtx .= False)
return pkg
where
modNameD = stringS modName
usedTys = concatMap mkUsedTys hwtys
Expand Down Expand Up @@ -622,16 +629,15 @@ verilogType t_ = do
Mon (tyCache %= HashSet.insert t)
let logicOrWire | isBiSignalIn t = "wire"
| otherwise = "logic"
pkgCtx <- Mon $ use tyPkgCtx
nm <- Mon $ use modNm
let pvrType = if pkgCtx
then tyName t
else stringS nm <> "_types::" <> tyName t
case t of
Product {} -> do
nm <- Mon $ use modNm
stringS nm <> "_types::" <> tyName t
Vector _ _ -> do
nm <- Mon $ use modNm
stringS nm <> "_types::" <> tyName t
RTree _ _ -> do
nm <- Mon $ use modNm
stringS nm <> "_types::" <> tyName t
Product {} -> pvrType
Vector {} -> pvrType
RTree {} -> pvrType
Signed n -> logicOrWire <+> "signed" <+> brackets (int (n-1) <> colon <> int 0)
Clock _ -> "logic"
Reset {} -> "logic"
Expand All @@ -648,12 +654,15 @@ verilogTypeMark :: HWType -> SystemVerilogM Doc
verilogTypeMark t_ = do
t <- normaliseType t_
Mon (tyCache %= HashSet.insert t)
pkgCtx <- Mon $ use tyPkgCtx
nm <- Mon $ use modNm
let m = tyName t
let pvrType = if pkgCtx
then tyName t
else stringS nm <> "_types::" <> tyName t
case t of
Product {} -> stringS nm <> "_types::" <> m
Vector _ _ -> stringS nm <> "_types::" <> m
RTree _ _ -> stringS nm <> "_types::" <> m
Product {} -> pvrType
Vector {} -> pvrType
RTree {} -> pvrType
_ -> emptyDoc

tyName :: HWType -> SystemVerilogM Doc
Expand Down Expand Up @@ -1187,29 +1196,31 @@ expr_ _ (DataTag (RTree _ _) (Right _)) = do

expr_ b (ConvBV topM t True e) = do
nm <- Mon $ use modNm
let nm' = stringS nm
pkgCtx <- Mon $ use tyPkgCtx
let prefix = if pkgCtx then stringS nm <> "_types::" else emptyDoc
case t of
Vector {} -> do
Mon (tyCache %= HashSet.insert t)
maybe (nm' <> "_types::" ) ((<> "_types::") . stringS) topM <>
maybe prefix ((<> "_types::") . stringS) topM <>
tyName t <> "_to_lv" <> parens (expr_ False e)
RTree {} -> do
Mon (tyCache %= HashSet.insert t)
maybe (nm' <> "_types::" ) ((<> "_types::") . stringS) topM <>
maybe prefix ((<> "_types::") . stringS) topM <>
tyName t <> "_to_lv" <> parens (expr_ False e)
_ -> expr b e

expr_ b (ConvBV topM t False e) = do
nm <- Mon $ use modNm
let nm' = stringS nm
pkgCtx <- Mon $ use tyPkgCtx
let prefix = if pkgCtx then stringS nm <> "_types::" else emptyDoc
case t of
Vector {} -> do
Mon (tyCache %= HashSet.insert t)
maybe (nm' <> "_types::" ) ((<> "_types::") . stringS) topM <>
maybe prefix ((<> "_types::") . stringS) topM <>
tyName t <> "_from_lv" <> parens (expr_ False e)
RTree {} -> do
Mon (tyCache %= HashSet.insert t)
maybe (nm' <> "_types::" ) ((<> "_types::") . stringS) topM <>
maybe prefix ((<> "_types::") . stringS) topM <>
tyName t <> "_from_lv" <> parens (expr_ False e)
_ -> expr b e

Expand Down

0 comments on commit ece7f26

Please sign in to comment.