Skip to content

Commit

Permalink
Merge pull request #2746 from clash-lang/mergify/copy/1.8/pr-2737
Browse files Browse the repository at this point in the history
Make sure clashSimulation is False in HDL even with -O2 (copy #2737)
  • Loading branch information
martijnbastiaan authored Jun 30, 2024
2 parents 6efdf62 + b305d8d commit a37ccb4
Show file tree
Hide file tree
Showing 7 changed files with 41 additions and 34 deletions.
4 changes: 3 additions & 1 deletion clash-prelude/src/Clash/Magic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,7 @@ module Clash.Magic
) where

import Data.String.Interpolate (__i)
import GHC.Magic (noinline)
import GHC.Stack (HasCallStack, withFrozenCallStack)
import Clash.NamedTypes ((:::))
import GHC.TypeLits (Nat,Symbol)
Expand Down Expand Up @@ -259,7 +260,8 @@ noDeDup = id

-- | 'True' in Haskell/Clash simulation. Replaced by 'False' when generating HDL.
clashSimulation :: Bool
clashSimulation = True
clashSimulation = noinline True
-- The 'noinline' is here to prevent SpecConstr from poking through the OPAQUE, see #2736
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE clashSimulation #-}

Expand Down
2 changes: 1 addition & 1 deletion tests/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -385,7 +385,7 @@ runClashTest = defaultMain $ clashTestRoot
, runTest "NameInstance" def{hdlSim=[]}
, outputTest "NameInstance" def
, outputTest "SetName" def{hdlTargets=[VHDL]}
, outputTest "SimulationMagic" def{hdlTargets=[VHDL]}
, outputTest "SimulationMagic2736" def{hdlTargets=[VHDL]}
, runTest "PatError" def{hdlSim=[]}
, runTest "ByteSwap32" def
, runTest "CharTest" def
Expand Down
10 changes: 7 additions & 3 deletions tests/clash-testsuite.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -102,7 +102,8 @@ library
-- Behaviour when loading modules can differ if the module is loaded from
-- an external interface file. See
-- https://github.com/clash-lang/clash-compiler/issues/1796 for an example.
shouldwork/LoadModules
shouldwork/LoadModules/precompiled
shouldwork/Basic/precompiled

exposed-modules:
Test.Tasty.Common
Expand All @@ -118,8 +119,11 @@ library
Test.Tasty.Vivado
Test.Tasty.Clash.CollectSimResults

-- From tests/shouldwork/LoadModules
T1796
-- From tests/shouldwork/LoadModules/precompiled
T1796a

-- From tests/shouldwork/Basic/precompiled
SimulationMagic2736a

other-modules:
Paths_clash_testsuite
Expand Down
Original file line number Diff line number Diff line change
@@ -1,16 +1,17 @@
module SimulationMagic where
{-# LANGUAGE TemplateHaskellQuotes #-}
{-# OPTIONS_GHC -O2 -fspec-constr #-}
module SimulationMagic2736 where

import Prelude as P
import Data.List (isInfixOf)
import System.Environment (getArgs)
import System.FilePath ((</>))

import Clash.Prelude
import Clash.Magic (clashSimulation)
import SimulationMagic2736a

f :: Int
f | clashSimulation = 123
| otherwise = 456
f = f0
{-# ANN f (defSyn "f") #-}

assertNotIn :: String -> String -> IO ()
Expand Down
8 changes: 8 additions & 0 deletions tests/shouldwork/Basic/precompiled/SimulationMagic2736a.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
{-# OPTIONS_GHC -O2 -fspec-constr #-}
module SimulationMagic2736a where

import Clash.Prelude

f0 :: Int
f0 | clashSimulation = 123
| otherwise = 456
27 changes: 2 additions & 25 deletions tests/shouldwork/LoadModules/T1796.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,29 +4,6 @@

module T1796 where

import Clash.Prelude
import T1796a

import Clash.Explicit.Testbench

topEntity
:: Signal System Bool
-> Signal System Bool
topEntity = id
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE topEntity #-}

tb
:: Signal System Bool
tb = done
where
testInput = stimuliGenerator clk rst (singleton True)
expectOutput = outputVerifier' clk rst (singleton True)
done = expectOutput $ topEntity testInput
clk = tbClockGen @System (not <$> done)
rst = resetGen @System
{-# INLINE tb #-}

testBench :: Signal System Bool
testBench = tb
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE testBench #-}
topEntity = tb
15 changes: 15 additions & 0 deletions tests/shouldwork/LoadModules/precompiled/T1796a.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TypeApplications #-}

module T1796a where

import Clash.Explicit.Prelude
import Clash.Explicit.Testbench

tb :: Signal System Bool
tb = done
where
done = register clk rst enableGen False $ id (pure True)
clk = tbClockGen @System (not <$> done)
rst = resetGen @System

0 comments on commit a37ccb4

Please sign in to comment.