Skip to content

Commit c3c9bff

Browse files
committed
Move xToBV to Clash.Sized.Internal.BitVector
1 parent e1f965d commit c3c9bff

File tree

6 files changed

+25
-21
lines changed

6 files changed

+25
-21
lines changed
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
CHANGED: `xToBV` is now located in `Clash.Sized.Internal.BitVector` to avoid circular dependencies.

clash-ghc/src-ghc/Clash/GHC/Evaluator/Primitive.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -43,6 +43,7 @@ import Data.Proxy (Proxy)
4343
import Data.Reflection (reifyNat)
4444
import Data.Text (Text)
4545
import qualified Data.Text as Text
46+
import Data.Text.Extra (showt)
4647
import GHC.Exts (IsList(..))
4748
import GHC.Float
4849
import GHC.Int
@@ -202,7 +203,7 @@ ghcPrimUnwind tcm p tys vs v [e] m0
202203
, "Clash.Sized.Vector.replace_int"
203204
, "GHC.Classes.&&"
204205
, "GHC.Classes.||"
205-
, "Clash.Class.BitPack.Internal.xToBV"
206+
, showt 'BitVector.xToBV
206207
, "Clash.Sized.Vector.imap_go"
207208
]
208209
= if isUndefinedPrimVal v then
@@ -2444,7 +2445,7 @@ ghcPrimStep tcm isSubj pInfo tys args mach = case primName pInfo of
24442445
val = unpack (toBV i :: BitVector 64)
24452446
in reduce (mkDoubleCLit tcm val resTy)
24462447

2447-
"Clash.Class.BitPack.Internal.xToBV"
2448+
"Clash.Sized.Internal.BitVector.xToBV"
24482449
| isSubj
24492450
, Just (nTy, kn) <- extractKnownNat tcm tys
24502451
-- The second argument to `xToBV` is always going to be suspended.

clash-lib/prims/common/Clash_Class_BitPack.primitives.yaml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,7 @@
2727
template: ~ARG[0]
2828
workInfo: Never
2929
- BlackBox:
30-
name: Clash.Class.BitPack.Internal.xToBV
30+
name: Clash.Sized.Internal.BitVector.xToBV
3131
kind: Expression
3232
type: 'xToBV :: KnownNat n => BitVector n -> BitVector n'
3333
template: ~ARG[1]

clash-lib/src/Clash/Normalize/Transformations/Inline.hs

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@
22
Copyright : (C) 2012-2016, University of Twente,
33
2016-2017, Myrtle Software Ltd,
44
2017-2022, Google Inc.,
5-
2021-2022, QBayLogic B.V.
5+
2021-2024, QBayLogic B.V.
66
License : BSD2 (see the file LICENSE)
77
Maintainer : QBayLogic B.V. <[email protected]>
88
@@ -14,6 +14,7 @@
1414
{-# LANGUAGE LambdaCase #-}
1515
{-# LANGUAGE MagicHash #-}
1616
{-# LANGUAGE MultiWayIf #-}
17+
{-# LANGUAGE NamedFieldPuns #-}
1718
{-# LANGUAGE OverloadedStrings #-}
1819
{-# LANGUAGE QuasiQuotes #-}
1920
{-# LANGUAGE TemplateHaskell #-}
@@ -48,7 +49,7 @@ import GHC.Stack (HasCallStack)
4849
import GHC.BasicTypes.Extra (isNoInline)
4950

5051
import qualified Clash.Explicit.SimIO as SimIO
51-
import qualified Clash.Sized.Internal.BitVector as BV (Bit(Bit), BitVector(BV))
52+
import qualified Clash.Sized.Internal.BitVector as BV (Bit(Bit), BitVector(BV), xToBV)
5253

5354
import Clash.Annotations.Primitive (extractPrim)
5455
import Clash.Core.DataCon (DataCon(..))
@@ -438,7 +439,8 @@ collapseRHSNoops _ (Letrec binds body) = do
438439
isNoopApp x (Prim PrimInfo{primWorkInfo=WorkIdentity i []},args) = do
439440
arg <- getTermArg (lefts args) i
440441
isNoopApp x (collectArgs arg)
441-
isNoopApp x (Prim PrimInfo{primName="Clash.Class.BitPack.Internal.xToBV"},args) = do
442+
isNoopApp x (Prim PrimInfo{primName},args)
443+
| primName == Text.showt 'BV.xToBV = do
442444
-- We don't make 'xToBV' something of 'WorkIdentity 1 []' because we don't
443445
-- want 'getIdentity' to replace "naked" occurances of 'xToBV' by
444446
-- 'unsafeCoerce#'. We don't want that since 'xToBV' has a special evaluator

clash-prelude/src/Clash/Class/BitPack/Internal.hs

Lines changed: 2 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
{-|
22
Copyright : (C) 2013-2016, University of Twente,
33
2016-2017, Myrtle Software Ltd,
4-
2021-2023 QBayLogic B.V.,
4+
2021-2024 QBayLogic B.V.,
55
2022, Google Inc.
66
License : BSD2 (see the file LICENSE)
77
Maintainer : QBayLogic B.V. <[email protected]>
@@ -26,7 +26,6 @@ module Clash.Class.BitPack.Internal where
2626

2727
import Prelude hiding (map)
2828

29-
import Control.Exception (catch, evaluate)
3029
import Data.Binary.IEEE754 (doubleToWord, floatToWord, wordToDouble,
3130
wordToFloat)
3231

@@ -44,16 +43,14 @@ import GHC.Generics
4443
import GHC.TypeLits (KnownNat, Nat, type (+), type (-))
4544
import GHC.TypeLits.Extra (CLog, Max)
4645
import Numeric.Half (Half (..))
47-
import System.IO.Unsafe (unsafeDupablePerformIO)
4846

4947
import Clash.Annotations.Primitive (hasBlackBox)
5048
import Clash.Class.BitPack.Internal.TH (deriveBitPackTuples)
5149
import Clash.Class.Resize (zeroExtend, resize)
5250
import Clash.Promoted.Nat (SNat(..), snatToNum)
5351
import Clash.Sized.Internal.BitVector
5452
(pack#, split#, checkUnpackUndef, undefined#, unpack#, unsafeToNatural, isLike#,
55-
BitVector, Bit, (++#))
56-
import Clash.XException
53+
BitVector, Bit, (++#), xToBV)
5754

5855
{- $setup
5956
>>> :m -Prelude
@@ -164,14 +161,6 @@ packXWith
164161
packXWith f = xToBV . f
165162
{-# INLINE packXWith #-}
166163

167-
xToBV :: KnownNat n => BitVector n -> BitVector n
168-
xToBV x =
169-
unsafeDupablePerformIO (catch (evaluate x)
170-
(\(XException _) -> return undefined#))
171-
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
172-
{-# CLASH_OPAQUE xToBV #-}
173-
{-# ANN xToBV hasBlackBox #-}
174-
175164
-- | Pack both arguments to a 'BitVector' and use
176165
-- 'Clash.Sized.Internal.BitVector.isLike#' to compare them. This is a more
177166
-- lentiant comparison than '(==)', behaving more like (but not necessarily

clash-prelude/src/Clash/Sized/Internal/BitVector.hs

Lines changed: 13 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@
22
Copyright : (C) 2013-2016, University of Twente,
33
2019 , Gergő Érdi
44
2016-2019, Myrtle Software Ltd,
5-
2021-2022, QBayLogic B.V.
5+
2021-2024, QBayLogic B.V.
66
2023 , Nadia Chambers
77
License : BSD2 (see the file LICENSE)
88
Maintainer : QBayLogic B.V. <[email protected]>
@@ -131,10 +131,12 @@ module Clash.Sized.Internal.BitVector
131131
, undefError
132132
, checkUnpackUndef
133133
, bitPattern
134+
, xToBV
134135
)
135136
where
136137

137138
import Control.DeepSeq (NFData (..))
139+
import Control.Exception (catch, evaluate)
138140
import Control.Lens (Index, Ixed (..), IxValue)
139141
import Data.Bits (Bits (..), FiniteBits (..))
140142
import Data.Data (Data)
@@ -183,6 +185,7 @@ import Language.Haskell.TH (Quote)
183185
#else
184186
import Language.Haskell.TH (TypeQ)
185187
#endif
188+
import System.IO.Unsafe (unsafeDupablePerformIO)
186189
import Test.QuickCheck.Arbitrary (Arbitrary (..), CoArbitrary (..),
187190
arbitraryBoundedIntegral,
188191
coarbitraryIntegral, shrinkIntegral)
@@ -194,7 +197,7 @@ import Clash.Class.Resize (Resize (..))
194197
import Clash.Promoted.Nat
195198
(SNat (..), SNatLE (..), compareSNat, snatToInteger, snatToNum, natToNum)
196199
import Clash.XException
197-
(ShowX (..), NFDataX (..), errorX, isX, showsPrecXWith, rwhnfX)
200+
(ShowX (..), NFDataX (..), errorX, isX, showsPrecXWith, rwhnfX, XException(..))
198201

199202
import Clash.Sized.Internal.Mod
200203

@@ -1605,3 +1608,11 @@ bitPattern s = [p| ((\_x -> $preprocess) -> $tuple) |]
16051608
| otherwise = error $
16061609
"Invalid bit pattern: " ++ show c ++
16071610
", expecting one of '0', '1', '.', '_', or a lowercase alphabetic character"
1611+
1612+
xToBV :: KnownNat n => BitVector n -> BitVector n
1613+
xToBV x =
1614+
unsafeDupablePerformIO (catch (evaluate x)
1615+
(\(XException _) -> return undefined#))
1616+
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
1617+
{-# CLASH_OPAQUE xToBV #-}
1618+
{-# ANN xToBV hasBlackBox #-}

0 commit comments

Comments
 (0)