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
The below program runs fine in GHCi, but when compiled and run, fails after the first invocation of sim:
module Main where
import Clash.Prelude
import Control.Arrow.Transformer.Automaton
circuit :: (HiddenClockResetEnable dom) => Signal dom Int -> Signal dom Int
circuit x = register 0 x
sim :: Int -> Int
sim x = start (signalAutomaton @System circuit) x
where
start (Automaton step) x = load sim x
where
(_, sim) = step 0
load (Automaton step) x = consume sim
where
(_, sim) = step x
consume (Automaton step) = output
where
(output, sim) = step 0
main :: IO ()
main = do
print $ sim 1
print $ sim 3
1
bug: user error (signalAutomaton: non-affine use of continuation)
The text was updated successfully, but these errors were encountered:
On Slack's #Clash, @christiaanb recommended trying -O0 which indeed is an effective workaround, however, I'm worried what its effect on simulation performance is.
I have also tried adding {-# OPAQUE sim #-} as per his recommendation but that does not fix the problem.
The below program runs fine in GHCi, but when compiled and run, fails after the first invocation of
sim
:The text was updated successfully, but these errors were encountered: