You signed in with another tab or window. Reload to refresh your session.You signed out in another tab or window. Reload to refresh your session.You switched accounts on another tab or window. Reload to refresh your session.Dismiss alert
<no location info>: error:
Other error:
divide by zero
if I compile the code attached below with clash Top.hs --verilog -fclash-spec-limit=100. Simulation of the topEntity works fine. It also works, if I replace the 26 in topEntity by 25 or any smaller value. Unfortunately, I could not come up with a smaller reproducer so far.
Reproducer: Top.hs
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
moduleTopwhereimportClash.PreludeimportControl.MonadimportData.ConstraintimportData.ProxyimportData.Type.BoolimportData.Type.EqualityimportGHC.TypeLits.KnownNatimportUnsafe.CoercetopEntity::HiddenClockResetEnableSystem=>SignalSystemBool
topEntity
= toSignal
$ distributeStages (SNat@26) False (repeat@64id)
$ fromSignal
$pureTrue--| Evenly distributes @d@ registers between @n@ combinational-- computations. The registers are all initialized with the provided-- initial value. The introduced delay is tracked using 'DSignal'.distributeStages::forall (d::Nat) (n::Nat) (a::Type).
(KnownNatn, NFDataXa) =>SNatd->a->Vecn (a->a) ->forall (dom::Domain) (k::Nat).
(KnownDomaindom, HiddenClockResetEnabledom) =>DSignaldomka->DSignaldom (k+d) a
distributeStages d@SNat x = distributeStages' d0 d
wheredistributeStages'::forall (m::Nat) (i::Nat) (r::Nat).
(KnownNatm, NFDataXa) =>SNati->SNatr->Vecm (a->a) ->forall (dom::Domain) (k::Nat).
(KnownDomaindom, HiddenClockResetEnabledom) =>DSignaldomka->DSignaldom (k+r) a
distributeStages' i@SNat r@SNat cs =case toUNat @mSNatofUZero-> delayedI x
USucc _ ->case toUNat r ofUZero->fmap (head cs)
. distributeStages' (succSNat i) r (tail cs)
USucc _ |Dict<- atMostOnePerStage @m@d@i
, Dict<- leTrans @(DistributedStagesmdi) @1@(r-1+1)
-> delayedI @(DistributedStagesmdi) x
.fmap (head cs)
. distributeStages'
(succSNat i)
(SNat@(r-DistributedStagesmdi))
(tail cs)
-- We never distribute more than one register per stage. The-- property trivially holds, as the only possible return values of-- 'DistributedStages' are zero or one.atMostOnePerStage::forallxyz.Dict (DistributedStagesxyz<=1)
atMostOnePerStage = unsafeCoerce (Dict::Dict (0<=0))
-- We don't use any dictionaries of 'Data.Constraint.Nat', as they suffer-- from https://github.com/clash-lang/clash-compiler/issues/2376leTrans::forallxyz. (y<=z, x<=y) =>Dict (x<=z)
leTrans = unsafeCoerce (Dict::Dict (0<=0))
--| A type family for calculating the positions at which we need to-- put a register in front, if we like to evenly distribute m-- registers between a chain of n circuit blocks, where m < n.-- Unfortunately, there are a lot of repetitions, as we don't -- have let bindings in type families. See the 'KnownNat3'-- instance below for a more readable version.typeDistributedStages::Nat->Nat->Nat->NattypefamilyDistributedStagesndiwhereDistributedStages_0_=0DistributedStagesndi=If (n<=?d)
1
( If ( 1<=?i--^ we don't place a register before the first element&&If (i<=?Modn (d+1) * (Divn (d+1) +1))
--^ distribute the hangover blocks to the first r chains
(Modi (Divn (d+1) +1) ==0)
(Mod
(i-Modn (d+1) * (Divn (d+1) +1))
(Divn (d+1)) ==0)
)
10
)
instance
(KnownNatn, KnownNatm, KnownNati) =>KnownNat3$(nameToSymbol ''DistributedStages) nmiwhere
natSing3 =let
n = natToNatural @n
m = natToNatural @m
i = natToNatural @i
r = f n m i
inSNatKn r
wheref::Nat->Nat->Nat->Nat
f n m i
| n ==0=0| n <= m =1|otherwise=let k = n `div` (m +1)
r = n `mod` (m +1)
b = (k +1) * r
inif1<= i &&if i <= b
thenmod i (k +1) ==0elsemod (i - b) k ==0then1else0
{-# INLINE natSing3 #-}
--| Some quick test code for seeing the 'DistributedStages' type -- family in action. This is only for those who like to understand-- the code. It is not required for reproducing the bug.placeRegister::Nat->Nat->IO()
placeRegister n m =doprint (k, r, b)
putStrLn"---"
forM_ chain $\(i, c) ->do
when c $putStrLn"[R]"putStr""print i
where-- minimum size of chained blocks without a register in between
k = n `div` (m +1)
-- number of hangover blocks
r = n `mod` (m +1)
-- add-one-more range bound
b = (k +1) * r
chain
| m <=0= ( , False) <$> [0..n-1]
| m >= n = (0, False) : (( , True) <$> [1..n-1])
|otherwise=
[ (i, i >0&& cond)
| i <- [0..n-1]
, let cond =if i <= b
then i `mod` (k +1) ==0else (i - b) `mod` k ==0
]
Also thanks to @leonschoorl for figuring out that there is no error when compiling Clash with GHC 9.10. This at least gives a workaround.
The text was updated successfully, but these errors were encountered:
I get some
if I compile the code attached below with
clash Top.hs --verilog -fclash-spec-limit=100
. Simulation of the topEntity works fine. It also works, if I replace the26
in topEntity by25
or any smaller value. Unfortunately, I could not come up with a smaller reproducer so far.Reproducer: Top.hs
Also thanks to @leonschoorl for figuring out that there is no error when compiling Clash with GHC 9.10. This at least gives a workaround.
The text was updated successfully, but these errors were encountered: