clash-lang / clash-compiler

Haskell to VHDL/Verilog/SystemVerilog compiler
https://clash-lang.org/
Other
1.42k stars 150 forks source link

None of my code ends up in the synthesized Verilog output #2542

Closed gergoerdi closed 1 year ago

gergoerdi commented 1 year ago

Given the following source code:

module Sudoku where

import Clash.Prelude
import Clash.Annotations.TH

import Data.Char (ord)

data Unique n
    = Unique (Index n)
    | Conflict
    | Unset
    deriving (Show)

getUnique :: (KnownNat n, n ~ k + 1) => BitVector n -> Unique n
getUnique = foldl propagate Unset . zip (reverse indicesI) . bv2v
  where
    propagate :: Unique n -> (Index n, Bit) -> Unique n
    propagate Unset      (i, b) | b == high = Unique i
                                | b == low  = Unset
    propagate (Unique i) (_, b) | b == low  = Unique i
    propagate _          _                  = Conflict

ascii :: Char -> Unsigned 8
ascii = fromIntegral . ord

topEntity
    :: "SW"  ::: BitVector 4
    -> "LED" ::: Unsigned 8
topEntity x = case getUnique x of
    Unset -> ascii '_'
    Unique i -> ascii '0' + 1 + fromIntegral i
    Conflict -> ascii '?'

makeTopEntity 'topEntity

In the simulator, this works as expected, which can be seen with e.g.

λ» fmap topEntity [minBound..maxBound]
[95,49,50,63,51,63,63,63,52,63,63,63,63,63,63,63]

Synthesizing this with Clash 1.6.5 completely discards all my code (!) and produces the following Verilog output:

/* AUTOMATICALLY GENERATED VERILOG-2001 SOURCE CODE.
** GENERATED BY CLASH 1.6.5. DO NOT MODIFY.
*/
`timescale 100fs/100fs
module topEntity
    ( // Inputs
      input [3:0] SW

      // Outputs
    , output wire [7:0] LED
    );

  assign LED = {8 {1'bx}};

endmodule
martijnbastiaan commented 1 year ago

Probably this:

reduceConst {49}
Changes when applying rewrite to:
zipWith @(Index 4) @Bit @(Index 4, Bit) @4
  ((,) @(Index 4) @Bit)
  (reverse @4 @(Index 4)
     (imap @4 @() @(Index 4) 4
        (λ(x :: Index 4) ->
        λ(ds :: ()) ->
        letrec
          result :: Index 4
          = x[LocalId]
        in result[LocalId])
        (replicate @4 @() (SNat @4 4) ())))
  (unsafeCoerce#
     @(Vec 4 (BitVector (BitSize Bit)))
     @(Vec 4 Bit)
     (unconcatBitVector# @4 @(BitSize Bit)
        (removedArg @Natural)
        (removedArg @Natural)
        x[LocalId]))
Result:
undefined @(Vec 4 (Index 4, Bit))

or this:

removeUnusedExpr {25}
Changes when applying rewrite to:
unconcatBitVector# @4 @(BitSize Bit)
  getUnique1[GlobalId]
  $fBitPackBit2[GlobalId]
  x[LocalId]
Result:
unconcatBitVector# @4 @(BitSize Bit)
  (removedArg @Natural)
  (removedArg @Natural)
  x[LocalId]
christiaanb commented 1 year ago

This works:

topEntity :: (Index 2, Index 2)
topEntity = case (indicesI @2) of
  (a `Cons` b `Cons` Nil) -> (a,b)

This doesn't:

topEntity :: (Index 2, Index 2)
topEntity = case reverse (indicesI @2) of
  (a `Cons` b `Cons` Nil) -> (a,b)
christiaanb commented 1 year ago

With #2543 I get:

-- Automatically generated VHDL-93
library IEEE;
use IEEE.STD_LOGIC_1164.ALL;
use IEEE.NUMERIC_STD.ALL;
use IEEE.MATH_REAL.ALL;
use std.textio.all;
use work.all;
use work.topEntity_types.all;

entity topEntity is
  port(SW  : in std_logic_vector(3 downto 0);
       LED : out unsigned(7 downto 0));
end;

architecture structural of topEntity is
  -- Test.hs:15:1-9
  signal ws                      : topEntity_types.array_of_Unique(0 to 4);
  -- Test.hs:15:1-9
  signal ws1                     : topEntity_types.array_of_Unique(0 to 3);
  signal result                  : topEntity_types.Unique;
  -- Test.hs:15:1-9
  signal \c$ws1_app_arg\         : topEntity_types.array_of_Tup2(0 to 3);
  -- Test.hs:15:1-9
  signal \c$ws1_app_arg_0\       : topEntity_types.array_of_std_logic(0 to 3);
  -- Test.hs:15:1-9
  signal \c$ws1_app_arg_1\       : topEntity_types.array_of_std_logic_vector_1(0 to 3);
  -- Test.hs:29:1-9
  signal i                       : topEntity_types.index_4;
  signal \c$app_arg\             : signed(63 downto 0);
  signal \c$vec2\                : topEntity_types.array_of_Unique(0 to 3);
  signal \c$ws1_app_arg_res\     : topEntity_types.array_of_index_4(0 to 3);
  signal \c$ws1_app_arg_res_res\ : topEntity_types.array_of_index_4(0 to 3);

begin
  ws <= topEntity_types.array_of_Unique'(topEntity_types.Unique'(std_logic_vector'("10" & "--")) & ws1);

  \c$vec2\ <= (ws(0 to ws'high - 1));

  -- zipWith begin
  zipWith : for i_1 in ws1'range generate
  begin
    fun_0 : block
      signal result_0                   : topEntity_types.Unique;
      signal \c$case_alt\               : topEntity_types.Unique;
      -- Test.hs:15:1-9
      signal i_0                        : topEntity_types.index_4;
      signal \c$case_alt_0\             : topEntity_types.Unique;
      signal \c$case_alt_1\             : topEntity_types.Unique;
      signal \c$case_scrut\             : boolean;
      -- Test.hs:15:1-9
      signal b                          : std_logic;
      signal \c$case_alt_selection_res\ : boolean;begin
      ws1(i_1) <= result_0;

      with (\c$vec2\(i_1)(3 downto 2)) select
        result_0 <= \c$case_alt_1\ when "00",
                    std_logic_vector'("01" & "--") when "01",
                    \c$case_alt\ when others;

      \c$case_alt_selection_res\ <= b = ('1');

      \c$case_alt\ <= std_logic_vector'("00" & (std_logic_vector(i_0))) when \c$case_alt_selection_res\ else
                      \c$case_alt_0\;

      i_0 <= \c$ws1_app_arg\(i_1).Tup2_sel0_index_4;

      \c$case_alt_0\ <= std_logic_vector'("10" & "--") when \c$case_scrut\ else
                        std_logic_vector'("01" & "--");

      \c$case_alt_1\ <= \c$vec2\(i_1) when \c$case_scrut\ else
                        std_logic_vector'("01" & "--");

      \c$case_scrut\ <= b = ('0');

      b <= \c$ws1_app_arg\(i_1).Tup2_sel1_std_logic;

    end block;
  end generate;
  -- zipWith end

  result <=  ws(ws'high) ;

  -- imap begin
  imap : block
    function max (l,r : in natural) return natural is
    begin
      if l > r then return l;
      else return r;
      end if;
    end function;
  begin
    imap_0 : for i_2 in \c$ws1_app_arg_res_res\'range generate
    begin
      \c$ws1_app_arg_res_res\(i_2) <= to_unsigned(i_2,max(1,integer(ceil(log2(real(4))))));

    end generate;
  end block;
  -- imap end

  -- reverse begin
  reverse_loop : for i_3 in 0 to (4 - 1) generate
    \c$ws1_app_arg_res\(\c$ws1_app_arg_res_res\'high - i_3) <= \c$ws1_app_arg_res_res\(i_3);
  end generate;
  -- reverse end

  -- zipWith begin
  zipWith_0 : for i_4 in \c$ws1_app_arg\'range generate
  begin
    \c$ws1_app_arg\(i_4) <= ( Tup2_sel0_index_4 => \c$ws1_app_arg_res\(i_4)
               , Tup2_sel1_std_logic => \c$ws1_app_arg_0\(i_4) );

  end generate;
  -- zipWith end

  -- map begin
  r_map : for i_5 in \c$ws1_app_arg_0\'range generate
  begin
    \c$ws1_app_arg_0\(i_5) <= \c$ws1_app_arg_1\(i_5)(0);

  end generate;
  -- map end

  -- unconcatBitVector begin
  unconcatBitVectorIter_loop : for i_6 in \c$ws1_app_arg_1\'range generate
    \c$ws1_app_arg_1\(\c$ws1_app_arg_1\'high - i_6) <= SW(((i_6 * 1) + 1 - 1) downto (i_6 * 1));
  end generate;
  -- unconcatBitVector end

  i <= topEntity_types.index_4'(topentity_types.fromSLV(result(1 downto 0)));

  \c$app_arg\ <= signed(std_logic_vector(resize(i,64)));

  with (result(3 downto 2)) select
    LED <= to_unsigned(49,8) + (resize(unsigned(std_logic_vector(\c$app_arg\)),8)) when "00",
           to_unsigned(63,8) when "01",
           to_unsigned(95,8) when others;

end;