Navigation Menu

Skip to content

Commit

Permalink
BlockRAM elements must be bit_vectors
Browse files Browse the repository at this point in the history
Otherwise Xilinx tools won't infer block rams.

Fixes #113
  • Loading branch information
christiaanb committed Jan 25, 2016
1 parent 0dd23a8 commit 1be0803
Show file tree
Hide file tree
Showing 9 changed files with 67 additions and 10 deletions.
4 changes: 4 additions & 0 deletions clash-lib/src/CLaSH/Backend.hs
Expand Up @@ -44,3 +44,7 @@ class Backend state where
expr :: Bool -> Expr -> State state Doc
-- | Bit-width of Int/Word/Integer
iwWidth :: State state Int
-- | Convert to a bit-vector
toBV :: HWType -> Text -> State state Doc
-- | Convert from a bit-vector
fromBV :: HWType -> Text -> State state Doc
8 changes: 7 additions & 1 deletion clash-lib/src/CLaSH/Netlist/BlackBox/Parser.hs
Expand Up @@ -82,6 +82,10 @@ pTagE = O <$ pToken "~RESULT"
<|> SigD <$> (pToken "~SIGD" *> pBrackets pSigD) <*> (Just <$> (pBrackets pNatural))
<|> (`SigD` Nothing) <$> (pToken "~SIGDO" *> pBrackets pSigD)
<|> IW64 <$ pToken "~IW64"
<|> (BV True) <$> (pToken "~TOBV" *> pBrackets pSigD) <*> (Just <$> pBrackets pNatural)
<|> (BV True) <$> (pToken "~TOBVO" *> pBrackets pSigD) <*> pure Nothing
<|> (BV False) <$> (pToken "~FROMBV" *> pBrackets pSigD) <*> (Just <$> pBrackets pNatural)
<|> (BV False) <$> (pToken "~FROMBVO" *> pBrackets pSigD) <*> pure Nothing

-- | Parse a bracketed text
pBrackets :: Parser a -> Parser a
Expand All @@ -102,7 +106,9 @@ pElemE = pTagE

-- | Parse SigD
pSigD :: Parser [Element]
pSigD = pSome (pTagE <|> pLimitedText)
pSigD = pSome (pTagE <|> pLimitedText
<|> (C <$> (pack <$> pToken "[ "))
<|> (C <$> (pack <$> pToken " ]")))

-- | Text excluding square brackets and tilde
pLimitedText :: Parser Element
Expand Down
1 change: 1 addition & 0 deletions clash-lib/src/CLaSH/Netlist/BlackBox/Types.hs
Expand Up @@ -32,6 +32,7 @@ data Element = C !Text -- ^ Constant
| IF !Element [Element] [Element]
| IW64 -- ^ Hole indicating whether Int/Word/Integer
-- are 64-Bit
| BV Bool [Element] (Maybe Int) -- ^ Convert to (True)/from(False) a bit-vector
| SigD [Element] !(Maybe Int)
deriving Show

Expand Down
20 changes: 20 additions & 0 deletions clash-lib/src/CLaSH/Netlist/BlackBox/Util.hs
Expand Up @@ -82,6 +82,7 @@ setSym i l
D (Decl n l') -> D <$> (Decl n <$> mapM (combineM setSym' setSym') l')
IF c t f -> IF <$> pure c <*> setSym' t <*> setSym' f
SigD e' m -> SigD <$> (setSym' e') <*> pure m
BV t e' m -> BV <$> pure t <*> setSym' e' <*> pure m
_ -> pure e
)

Expand All @@ -102,6 +103,7 @@ setClocks bc bt = mapM setClocks' bt
setClocks' (D (Decl n l)) = D <$> (Decl n <$> mapM (combineM (setClocks bc) (setClocks bc)) l)
setClocks' (IF c t f) = IF <$> pure c <*> setClocks bc t <*> setClocks bc f
setClocks' (SigD e m) = SigD <$> (setClocks bc e) <*> pure m
setClocks' (BV t e m) = BV <$> pure t <*> setClocks bc e <*> pure m

setClocks' (Clk Nothing) = let (clk,rate) = clkSyncId $ fst $ bbResult bc
clkName = Text.append clk (Text.pack (show rate))
Expand Down Expand Up @@ -261,6 +263,24 @@ renderTag b (L n) = let (s,_,_) = bbInputs b !! n
mkLit i = i

renderTag _ (Sym n) = return $ Text.pack ("n_" ++ show n)

renderTag b (BV True es (Just n)) = do
e' <- Text.concat <$> mapM (renderElem b) es
let (_,hty,_) = bbInputs b !! n
(displayT . renderOneLine) <$> toBV hty e'
renderTag b (BV True es Nothing) = do
e' <- Text.concat <$> mapM (renderElem b) es
let (_,hty) = bbResult b
(displayT . renderOneLine) <$> toBV hty e'
renderTag b (BV False es (Just n)) = do
e' <- Text.concat <$> mapM (renderElem b) es
let (_,hty,_) = bbInputs b !! n
(displayT . renderOneLine) <$> fromBV hty e'
renderTag b (BV False es Nothing) = do
e' <- Text.concat <$> mapM (renderElem b) es
let (_,hty) = bbResult b
(displayT . renderOneLine) <$> fromBV hty e'

renderTag b (Typ Nothing) = fmap (displayT . renderOneLine) . hdlType . snd $ bbResult b
renderTag b (Typ (Just n)) = let (_,ty,_) = bbInputs b !! n
in (displayT . renderOneLine) <$> hdlType ty
Expand Down
19 changes: 14 additions & 5 deletions clash-systemverilog/primitives/CLaSH.Prelude.BlockRam.json
Expand Up @@ -11,21 +11,30 @@
-> Signal' clk a"
, "templateD" :
"// blockRam begin
~SIGD[RAM_~SYM[0]][2];
~SIGD[dout_~SYM[1]][6];
typedef logic [~SIZE[~TYPO]-1:0] RAM_array_~SYM[4] [0:~LENGTH[~TYP[2]]-1];
RAM_array_~SYM[4] RAM_~SYM[0];
logic [~SIZE[~TYPO]-1:0] dout_~SYM[1];

function RAM_array_~SYM[4] init_to_bv_~SYM[2];
input ~SIGD[value][2];
begin
for (int i_~SYM[3]=0; i_~SYM[3]<~LENGTH[~TYP[2]]; i_~SYM[3]=i_~SYM[3]+1)
init_to_bv_~SYM[2][i_~SYM[3]] = ~TOBV[value[ i_~SYM[3] ]][6];
end
endfunction

initial begin
~SYM[0] = ~LIT[3];
RAM_~SYM[0] = init_to_bv_~SYM[2](~LIT[2]);
end

always @(posedge ~CLK[1]) begin : blockRam_~COMPNAME_~SYM[3]
if (~ARG[5]) begin
RAM_~SYM[0][~ARG[3]] <= ~ARG[6];
RAM_~SYM[0][~ARG[3]] <= ~TOBV[~ARG[6]][6];
end
dout_~SYM[1] <= RAM_~SYM[0][~ARG[4]];
end

assign ~RESULT = dout_~SYM[1];
assign ~RESULT = ~FROMBV[dout_~SYM[1]][6];
// blockRam end"
}
}
Expand Down
2 changes: 2 additions & 0 deletions clash-systemverilog/src/CLaSH/Backend/SystemVerilog.hs
Expand Up @@ -77,6 +77,8 @@ instance Backend SystemVerilogState where
inst = inst_
expr = expr_
iwWidth = use intWidth
toBV hty id_ = verilogTypeMark hty <> "_to_lv" <> parens (text id_)
fromBV hty id_ = fromSLV hty id_ (typeSize hty - 1) 0

type SystemVerilogM a = State SystemVerilogState a

Expand Down
2 changes: 2 additions & 0 deletions clash-verilog/src/CLaSH/Backend/Verilog.hs
Expand Up @@ -68,6 +68,8 @@ instance Backend VerilogState where
inst = inst_
expr = expr_
iwWidth = use intWidth
toBV _ = text
fromBV _ = text

type VerilogM a = State VerilogState a

Expand Down
19 changes: 15 additions & 4 deletions clash-vhdl/primitives/CLaSH.Prelude.BlockRam.json
Expand Up @@ -12,8 +12,19 @@
, "templateD" :
"-- blockRam begin
blockRam_~COMPNAME_~SYM[0] : block
signal RAM_~SYM[1] : ~TYP[2] := ~LIT[2];
signal dout_~SYM[2] : ~TYP[6];
type RamType is array(natural range <>) of std_logic_vector(~SIZE[~TYPO]-1 downto 0);

function init_to_bv (arg : in ~TYP[2]) return RamType is
variable RAM_init : RamType(0 to ~LENGTH[~TYP[2]]-1);
begin
for i in RAM_init'range loop
RAM_init(i) := ~TOBV[arg(i)][6];
end loop;
return RAM_init;
end function;

signal RAM_~SYM[1] : RamType (0 to ~LENGTH[~TYP[2]]-1) := init_to_bv(~LIT[2]);
signal dout_~SYM[2] : std_logic_vector(~SIZE[~TYP[6]]-1 downto 0);
signal wr_~SYM[3] : integer range 0 to ~LIT[0] - 1;
signal rd_~SYM[4] : integer range 0 to ~LIT[0] - 1;
begin
Expand All @@ -33,13 +44,13 @@ begin
begin
if rising_edge(~CLK[1]) then
if ~ARG[5] then
RAM_~SYM[1](wr_~SYM[3]) <= ~ARG[6];
RAM_~SYM[1](wr_~SYM[3]) <= ~TOBV[~ARG[6]][6];
end if;
dout_~SYM[2] <= RAM_~SYM[1](rd_~SYM[4]);
end if;
end process;

~RESULT <= dout_~SYM[2];
~RESULT <= ~FROMBVO[dout_~SYM[2]];
end block;
-- blockRam end"
}
Expand Down
2 changes: 2 additions & 0 deletions clash-vhdl/src/CLaSH/Backend/VHDL.hs
Expand Up @@ -68,6 +68,8 @@ instance Backend VHDLState where
inst = inst_
expr = expr_
iwWidth = use intWidth
toBV _ id_ = "toSLV" <> parens (text id_)
fromBV hty id_ = fromSLV hty id_ (typeSize hty - 1) 0

type VHDLM a = State VHDLState a

Expand Down

0 comments on commit 1be0803

Please sign in to comment.