How to implement Haskell code in Clash

66 views
Skip to first unread message

Farhad A

unread,
Jul 10, 2021, 1:38:26 PM7/10/21
to Clash - Hardware Description Language

Dear community,
I have been working on my thesis which is basically is about comparing HLS tools and compilers. As I am new to Clash, I have a question regarding the code below. I want to know how can implement this code which is compatible with Haskell compiler in Clash. I know that Clash does not support recursive, but is there a way to implement it in Clash?
Thanks in advance for your help.

module LUT where

css 0 = [[]]
css n = concat [[-1:cs, 1:cs] | cs <- css (n-1)]
tangent cs = truncate $ 1024 * (tan $ sum $ zipWith (*) bs cs)

lut :: Int -> [Int]
lut n = map tangent (css n)
--as = [45.0, 26.6, 14.0, 7.1, 3.6, 1.8, 0.9, 0.4, 0.2, 0.1]
as = (45.0:>26.6:>14.0:>7.1:>3.6:>1.8:>0.9:>0.4:>0.2:>0.1:>Nil)
--bs = [pi/180*x | x<-as]
bs = map (*(pi/180)) as

Peter Lebbing

unread,
Jul 11, 2021, 6:07:04 AM7/11/21
to Clash - Hardware Description Language
Hello Farhad!

> I know that Clash does not support recursive, but is there a way to
> implement it in Clash? Thanks in advance for your help.

> lut :: Int -> [Int]

The depth of the recursion and the size of vectors need to be known at
compile time. That means that the code could in principle be rewritten
to something of the form

lut :: KnownNat n => SNat n -> Vec [...] Int

but this highlights a "problem". This version of lut has no actual
inputs (SNat is a singleton, it is 0 bits wide). You would have to
specify an actual n before Clash can process it. So the result is a
constant. It doesn't seem that useful to implement a constant in
hardware; it's just a bunch of wires that are either connected to the
power supply or to ground.

To be precise, the function lut is unsynthesisable, to make it
synthesisable you would do

topEntity :: Vec [...] Int
topEntity = lut d5

or synonymously

topEntity :: Vec [...] Int
topEntity = lut (SNat :: SNat 5)

and this is a function with no inputs.

The input in your function lut is "structural": it determines the size
of the circuit.

I think the point is precisely that Clash is not high level synthesis.
Simplified, with Clash, you describe the transition function for a
single clock cycle of the memory elements, and the structure of your
Haskell code and the structure of the resultant hardware are similar.
That structure cannot depend on the value of the input.

With high level synthesis, it would be possible to construct such a
circuit, by unrolling it over time. But Clash only unrolls over space.

The match between structure in Clash source and structure in generated
hardware can also be a very good thing, as it allows control over that
structure. Maybe one day Clash will also do high level synthesis, but I
think it would be an addition to structural specification, allowing the
user to choose the tool best for the job for each part of their design.
However, this is just musing, Clash doesn't do HLS at this time.

HTH,

Peter.

Peter Lebbing

unread,
Jul 11, 2021, 6:20:16 AM7/11/21
to Clash - Hardware Description Language
On Sun, 11 Jul 2021, Peter Lebbing wrote:
> That means that the code could in principle be rewritten to something
> of the form

If you want, I can work that out for you, though. Do you want me to?

Peter.

Farhad A

unread,
Jul 11, 2021, 10:12:15 AM7/11/21
to Clash - Hardware Description Language
Hello Peter,
Thanks for your answer and explanation. In this LUT module, I just want to store tangent values, so as your said it contains a list of constant values of tangent theta and using them in another module called "Update" that I've attached it as well below. Basically, I have to implement some non trivial applications in Clash and other HLS languages (e.g. SystemC) and make comparison between them in case of performance. I am trying to implement MUSIC algorithm based on a thesis which has been done in University of Twente. I would be grateful if you could help me on how to implement an equivalent of this LUT module in Clash that can be used in "Update" module. I appreciate your consideration.
Best,
Farhad

module Update where
import Clash.Prelude
import LUT
import Resize

type UpdateI1 = (Signed 16, Signed 16, Signed 16)
type UpdateI2 = Vec 10 Bit
type UpdateO  = (Signed 16, Signed 16)

update :: UpdateI1 -> UpdateI2 -> UpdateO
update (a, b, c) ds = (b', c')   
 where
  tanv = getTan (unpack (reverse ds))
  tmp = mytrunc $ scale $ (myext a)*(myext tanv)
  b' = b + tmp
  c' = c - tmp

getTan :: Unsigned 10 -> Signed 16
getTan n = reverse $(listToVecTH(lut 10)) ! n

scale x = shiftR x 10

Farhad A

unread,
Jul 11, 2021, 10:28:26 AM7/11/21
to Clash - Hardware Description Language
Also here is the block diagram of the LUT in which a set of di is mapped to tangent theta.
Farhad
Capture.PNG

Peter Lebbing

unread,
Jul 11, 2021, 11:03:08 AM7/11/21
to Clash - Hardware Description Language
Hello Farhad,

> Thanks for your answer and explanation. In this LUT module, I just
> want to store tangent values, so as you said it contains a list of
> constant values of tangent theta and I want to use these values in
> another module called "update" which I attached it as well.

> getTan :: Unsigned 10 -> Signed 16
> getTan n = reverse $(listToVecTH(lut 10)) ! n

Ah! This should already work just fine, both in simulation and in
hardware. The $(...) construct is Template Haskell, which can do
term-level computation and then use the result as part of the syntax
tree of the program to be compiled. So here, you compute, at
compile-time, the constant vector with the constants generated by `lut`.
This compilation stage is just standard Haskell where you're free to use
lists.

The only thing preventing the code to compile right now is that you
defined `lut` as [Int] whereas here it should be [Signed 16]. Also, (!)
is the wrong indexing function, you want (!!). I would also put the
reverse inside the Template Haskell; it's not necessary, but why compute
a vector at compile time and then reverse it at runtime?

So

getTan :: Unsigned 10 -> Signed 16
getTan n = $(listToVecTH . reverse $ lut 10) !! n

Also, I see you wrote

tanv = getTan (unpack (reverse ds))

but `unpack` expects a BitVector, not a Vec n Bit. They're
different :-). You mean

tanv = getTan (bitCoerce (reverse ds))

(bitCoerce is just (unpack . pack) )

I also wonder if you actually need to specify ds as a `Vec 10 Bit` or it
would be better to immediately declare it `Unsigned 10`. In the
generated HDL, they might very well be the exact same thing. You should
verify the bit endianness though; you might end up using the
`Vec 10 Bit` anyway to reverse endianness if that is necessary.

I hope this gives you enough to work with, feel free to ask more
questions.

Oh, one final thing. You might hit compilation speed issues with long
vectors. I actually just needed to use a lookup ROM construction myself
because Clash would stumble on the length of my vector. Your `getTan`
lends itself perfectly to that construction, and while the solution is a
bit hacky, it has no trouble with long vectors. So if you need that, I
can show you how to work around it.

HTH,

Peter.

Farhad A

unread,
Jul 11, 2021, 11:52:13 AM7/11/21
to Clash - Hardware Description Language
Hello Peter,
I appreciate your kindness in explaining the problem. I made those modifications you mentioned but still it prevents the compilation. I have attached my source code below, Could you please take a look if you don't mind? Again sorry for disturbing you and thanks for your patience.
Regards,
Farhad
Resize.hs
LUT.hs
Update.hs

Farhad A

unread,
Jul 11, 2021, 12:28:03 PM7/11/21
to Clash - Hardware Description Language
Also regarding your issue about ds specification, I should say that ds is the output of another function which generates Vec 10 Bit, So thats why I used Vec 10 Bit.

Farhad

Peter Lebbing

unread,
Jul 11, 2021, 1:55:02 PM7/11/21
to Clash - Hardware Description Language
Hello Farhad,

> I made those modifications you mentioned but still it prevents the
> compilation.

When I have the time, I'll look at it more but it suddenly occurred to
me I made a mistake. The `reverse` from the Clash Prelude works on
`Vec`, but as I moved it inside the Template Haskell you need the one
from the Haskell Prelude that works on lists:

import qualified Prelude as P

getTan :: Unsigned 10 -> Signed 16
getTan n = $(listToVecTH . P.reverse $ lut 10) !! n

I'll look at the rest of the code later, and see if there are any more
small problems preventing compilation.

Sorry for my oversight!

> Again sorry for disturbing you and thanks for your patience.

No need to apologise, this is what we have the list for! :-)

HTH,

Peter.

Farhad A

unread,
Jul 12, 2021, 1:49:04 AM7/12/21
to Clash - Hardware Description Language
Hi Peter,
Thanks for your last comment which helps me to find the issue. I forgot to add to "import Prelude" in LUT module. Thats why the compiler was complaining. I made the new changes as well and now it works properly. Thanks for your great help and I think I will face more issues for writing testbench and completing the whole application, so I will ask more questions if you don't mind :-).
Best Regards,
Farhad

Peter Lebbing

unread,
Jul 12, 2021, 7:30:43 AM7/12/21
to Clash - Hardware Description Language
Hi Farhad,

> [...] and I think I will face more issues for writing testbench and
> completing the whole application, so I will ask more questions if you
> don't mind :-).

I'm glad you found the issue! Feel free to ask more in the future!

Warm regards,

Peter.
Reply all
Reply to author
Forward
0 new messages