news

netlist-to-vhdl converts a Netlist AST (Abstract Syntax Tree) to VHDL (VHSIC Hardware Description Language). It is now available in Fedora. Install it using:

 $ sudo yum install ghc-netlist-to-vhdl-devel

The genVHDL function accepts a Netlist.AST module and emits VHDL. For example:

{-# LANGUAGE ParallelListComp #-}

import Language.Netlist.AST
import Language.Netlist.Util
import Language.Netlist.GenVHDL

t :: Module
t = Module "foo" (f ins) (f outs) [] ds
  where
    f xs = [ (x, makeRange Down sz) | (x, sz) <- xs ]
    ins = [("clk", 1), ("reset", 1), ("enable", 1), ("x", 16)]
    outs = [("z", 16)]

ds :: [Decl]
ds = [ NetDecl "a" (makeRange Down 16) (Just (ExprVar "x"))
     , NetDecl "b" (makeRange Down 16) (Just (sizedInteger 16 10))
     , MemDecl "c" Nothing (makeRange Down 16) Nothing
     , ProcessDecl (Event (ExprVar "clk") PosEdge)
                   (Just (Event (ExprVar "reset") PosEdge, 
		   	(Assign (ExprVar "c") (sizedInteger 16 0))))
                   (If (ExprVar "enable")
                         (Assign (ExprVar "c") (ExprVar "x"))
                         Nothing)
     ]

main = do
        putStrLn $ genVHDL t ["work.all"]

The above code can be compiled and run using:

$ ghc --make Example.hs

$ ./Example

When executed it will generate the following VHDL:

library IEEE;
use IEEE.STD_LOGIC_1164.ALL;
use IEEE.NUMERIC_STD.ALL;
use work.all;
entity foo is
  port(clk : in std_logic;
       reset : in std_logic;
       enable : in std_logic;
       x : in std_logic_vector(15 downto 0);
       z : out std_logic_vector(15 downto 0));
end entity foo;
architecture str of foo is
  signal a : std_logic_vector(15 downto 0) := x;
  signal b : std_logic_vector(15 downto 0) := "0000000000001010";
  signal c : std_logic_vector(15 downto 0);
begin
  proc3 : process(clk,reset) is
  begin
    if reset = '1' then
      c <= "0000000000000000";
    elsif rising_edge(clk) then
      if enable then
        c <= x;
      end if;
    end if;
  end process proc3;
end architecture str;