Skip to content

Commit

Permalink
Merge pull request #2900 from clash-lang/add-nfdatax-simonly
Browse files Browse the repository at this point in the history
Add `NFDataX (SimOnly a)`
  • Loading branch information
martijnbastiaan authored Mar 6, 2025
2 parents db19820 + 773ae8d commit 207cb91
Show file tree
Hide file tree
Showing 2 changed files with 8 additions and 4 deletions.
1 change: 1 addition & 0 deletions changelog/2025-03-06T11_10_03+01_00_add_nfdatax_simonly
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
ADDED: Added instance `NFDataX (SimOnly a)`
11 changes: 7 additions & 4 deletions clash-prelude/src/Clash/Magic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ Refer to "Clash.Annotations.TopEntity" for controlling naming of entities
-}

{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskellQuotes #-}

Expand All @@ -43,13 +44,15 @@ module Clash.Magic
, clashCompileError
) where

import Clash.Annotations.Primitive (Primitive(..), hasBlackBox)
import Clash.NamedTypes ((:::))
import Clash.Promoted.Symbol (SSymbol)
import Clash.XException (NFDataX)
import Data.String.Interpolate (__i)
import GHC.Generics (Generic)
import GHC.Magic (noinline)
import GHC.Stack (HasCallStack, withFrozenCallStack)
import Clash.NamedTypes ((:::))
import GHC.TypeLits (Nat,Symbol)
import Clash.Promoted.Symbol (SSymbol)
import Clash.Annotations.Primitive (Primitive(..), hasBlackBox)

-- | Prefix instance and register names with the given 'Symbol'
prefixName
Expand Down Expand Up @@ -272,7 +275,7 @@ clashSimulation = noinline True
-- * Co-simulation state or meta-data
-- * etc.
data SimOnly a = SimOnly a
deriving (Eq, Ord, Foldable, Traversable)
deriving (Generic, Eq, Ord, Foldable, Traversable, NFDataX)
{-# ANN SimOnly hasBlackBox #-}

instance Functor SimOnly where
Expand Down

0 comments on commit 207cb91

Please sign in to comment.