HHDL, the first English post about it.

Dec 05, 2011 02:07

HHDL grew out of my desire to express everything in Haskell. So at least one H in HHDL stands for Haskell. Other three letters, H, D and L, stand for Hardware Description Language. HHDL tries to express computer hardware in Haskell, that's its part of everything.

Also it is pun on VHDL.

There are plenty of Haskell libraries for hardware description. But few, if any, of them provide support for algebraic types and pattern matching. Also, they mostly quite light on adding state to circuits, which is bad because state should be controlled. As I found ADT, pattern matching and restriction on state quite handy, I decided I should create my own implementation.

Let me go straight to example. A circuit that accumulate sum from input which have type Maybe Word8:
-- Many extensions. I overload many things from Haskell Prelude in the style
-- of Awesome Prelude. Also you may need a Template Haskell transformations
-- on declarations, which derives classes and type families instances, etc, etc.
{-# LANGUAGE TypeFamilies, TypeOperators, FlexibleContexts, DoRec #-}
{-# LANGUAGE DeriveDataTypeable, NoImplicitPrelude, TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-}

module Hardware.HHDL.Examples.RunningSumMaybes where

import Data.Word

-- The main module of the library. It exports everything I deemed useful
-- for hardware description - code generation over ADT, netlist operators, some
-- handy functions from Prelude...
-- Also, it contains making of wires for Either and Maybe and matching functions.
import Hardware.HHDL

-- The description of clocking frequency for our example.
import Hardware.HHDL.Examples.Clock

-------------------------------------------------------------------------------
-- How to pattern match an algebraic type.

-- Clocked is a type of entity. It has three arguments: a list of clocking frequencies allowed
-- in netlist, types of inputs and outputs.
runningSumMaybes :: Clock c => Clocked (c :. Nil) (Wire c (Maybe Word8) :. Nil) (Wire c Word8 :. Nil)
runningSumMaybes = mkClocked "runningSumMaybes" $ \(mbA :. Nil) -> do
-- here we pattern match in the "First class patterns" style.
-- the idea is that for each constructor Cons of algebraic type T we automatically
-- create two functions:
-- - mkCons which creates a wire (of type Wire c T) from wires of arguments and
-- - pCons which matches a wire of type Wire c T with patterns of types of Cons
-- arguments.
-- pJust and pNothing were generated in Hardware.HHDL.HHDL from the description of
-- Maybe type.
-- pvar is a pattern that matches anything and passes that anything as an argument
-- to processing function.
a <- match mbA [
-- if we have Just x, return it!
pJust pvar --> \(x :. Nil) -> return x
-- default with 0, if Nothing.
, pNothing --> \Nil -> return (constant 0)
]
rec
-- lock current sum at the clocking frequency edge.
sum <- register 0 nextSum
-- compute the sum.
nextSum <- assignWire (sum + a)
-- return currently locked sum.
return $ sum :. Nil

-- How to obtain VHDL text - we fix polymorphic parameters in Clocked, generate text (with any
-- entities we have to use) and pass it to display and write function.
runningSumMaybesVHDLText = writeHDLText VHDL (runningSumMaybes :: Clocked (Clk :. Nil) (Wire Clk (Maybe Word8) :. Nil) (Wire Clk Word8 :. Nil))
(\s -> putStrLn s >> writeFile "runningSumMaybes.vhdl" s)

-- a shortcut.
test = runningSumMaybesVHDLText
If you run ghci-6.12.1 -isrc Hardware.HHDL.Examples.RunningSumMaybes, and at the prompt type test, you will see generated VHDL text (Verilog support under way).

The text is here, I commented it:
-------------------------------------------------------------------------------
-- Entity declaration and architecture for runningSumMaybes_1.

entity runningSumMaybes_1 is
port map (
-- an input of type Maybe Word8. The Maybe type contains only two constructors
-- so we have to add only one bit to Word8 to discriminate between Nothing and Just.
generated_temporary_name_0 : in bit_vector (8 downto 0);
-- the result.
generated_temporary_name_4 : out bit_vector (7 downto 0);
-- clocks and resets. They added and passed to lower level entities automatically.
Hardware_HHDL_Examples_Clock_Clk: in std_logic;
Hardware_HHDL_Examples_Clock_Reset: in std_logic
);
end entity runningSumMaybes_1;

architecture hhdl_generated of runningSumMaybes_1 is

-- two pattern-matching support functions.
pure function select(s : in bit; t, f : in bit) return bit is
begin
if s = '1' then
return t;
else
return f;
end function select;

pure function select(s : in bit; t, f : in bit_vector) return bit_vector is
begin
if s = '1' then
return t;
else
return f;
end function select;

-- all temporary signals.
signal generated_temporary_name_5 : bit_vector(0 to 7);
signal generated_temporary_name_1 : bit_vector(0 to 8);
signal generated_temporary_name_3 : bit;
signal generated_temporary_name_2 : bit;
begin
-- adding latched "sum" wire and the result of pattern match.
-- I made a few edits to make select call from pattern matching more readable
generated_temporary_name_5 <= (generated_temporary_name_4 +
select(
-- "if isJust generated_temporary_name_0 ..."
("1" and generated_temporary_name_2),
-- "take least 8 bits from generated_temporary_name_1 (ie, out input, see below)"
( generated_temporary_name_1 ) ( 7 downto 0 )(7 downto 0),
-- otherwise, default to vector of all zeroes.
"00000000"
)
);
-- the clocking machinery.
-- it is generated from "register resetValue wireToLatch".
-- the precise details like positive/negative reset, rising/falling edge latching
-- they all specified in the instance of Clock class for Clk type.
process (Hardware_HHDL_Examples_Clock_Clk, Hardware_HHDL_Examples_Clock_Reset) is
begin
if not Hardware_HHDL_Examples_Clock_Reset then
generated_temporary_name_4 <= "00000000";
else if rising_edge(Hardware_HHDL_Examples_Clock_Clk) then
generated_temporary_name_4 <= generated_temporary_name_5;
end if;
end process;
generated_temporary_name_1 <= generated_temporary_name_0;
-- isNothing generated_temporary_name_0
generated_temporary_name_3 <= (( generated_temporary_name_1 ) ( 8 downto 8 ))=("0");
-- isJust generated_temporary_name_0
generated_temporary_name_2 <= (( generated_temporary_name_1 ) ( 8 downto 8 ))=("1");
end architecture hhdl;
Here it is! Not 100% correct, but quite close to it. ;)

Wire type in HHDL parametrized by clock frequency and value carried: data Wire c a.

Most operations performed on values with the same clock frequency, like +:
*Hardware.HHDL.Examples.RunningSumMaybes> :i Arith
class Arith op where
(+) :: op -> op -> ArithResult op
(*) :: op -> op -> ArithResult op
(-) :: op -> op -> ArithResult op
-- Defined at src\Hardware\HHDL\HDLPrelude.hs:22:6-10
instance [overlap ok] Arith Int
-- Defined at src\Hardware\HHDL\HDLPrelude.hs:71:9-17
instance [overlap ok] Arith Integer
-- Defined at src\Hardware\HHDL\HDLPrelude.hs:77:9-21
instance [overlap ok] Arith Word8
-- Defined at src\Hardware\HHDL\HDLPrelude.hs:99:9-19
instance [overlap ok] (BitRepr ty,
Arith ty,
BitRepr (ArithResult ty)) =>
Arith (Wire c ty)
-- Defined at src\Hardware\HHDL\HHDL.hs:129:9-77So you cannot accidentally pass wires from one clock frequency domain into another clock frequency domain. You will have to use special adaptor, like FIFO.

The code at the right side of --> operator is also restricted. You cannot put register's here, it "executes" (defines hardware netlist parts) without any defined clock frequency domains. So you cannot remember some wrong value from incorrect pattern match and use it to do harm.

That division between stateful and pure combinational circuits is one of my favorites. I think it will greatly simplify testing.

Right now I am working on interpretation of netlists so you could test your hardware from GHCi's prompt.

We'll see.

vhdl, english, haskell

Previous post Next post
Up