Skip to content

Commit 8510fbd

Browse files
committed
Add BitPack instance for Index 0
1 parent 1d49cd2 commit 8510fbd

File tree

1 file changed

+30
-5
lines changed
  • clash-prelude/src/Clash/Sized/Internal

1 file changed

+30
-5
lines changed

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

+30-5
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@ Maintainer : QBayLogic B.V. <devops@qbaylogic.com>
99
{-# LANGUAGE CPP #-}
1010
{-# LANGUAGE DeriveAnyClass #-}
1111
{-# LANGUAGE FlexibleContexts #-}
12+
{-# LANGUAGE FlexibleInstances #-}
1213
{-# LANGUAGE MultiParamTypeClasses #-}
1314
{-# LANGUAGE RoleAnnotations #-}
1415
{-# LANGUAGE TemplateHaskell #-}
@@ -21,6 +22,7 @@ Maintainer : QBayLogic B.V. <devops@qbaylogic.com>
2122
{-# OPTIONS_GHC -fplugin GHC.TypeLits.Normalise #-}
2223

2324
{-# OPTIONS_HADDOCK show-extensions not-home #-}
25+
{-# OPTIONS_GHC -fno-warn-orphans #-}
2426

2527
module Clash.Sized.Internal.Index
2628
( -- * Datatypes
@@ -75,8 +77,10 @@ import Prelude hiding (even, odd)
7577

7678
import Control.DeepSeq (NFData (..))
7779
import Data.Bits (Bits (..), FiniteBits (..))
80+
import Data.Constraint (Dict(..))
7881
import Data.Data (Data)
7982
import Data.Default.Class (Default (..))
83+
import Data.Proxy (Proxy(..))
8084
import Text.Read (Read (..), ReadPrec)
8185
import Text.Printf (PrintfArg (..), printf)
8286
import Data.Ix (Ix(..))
@@ -93,9 +97,11 @@ import Language.Haskell.TH (TypeQ)
9397
import GHC.Generics (Generic)
9498
import GHC.Natural (Natural, naturalFromInteger)
9599
import GHC.Natural (naturalToInteger)
100+
import GHC.Num.Integer (integerLog2)
96101
import GHC.Stack (HasCallStack)
97102
import GHC.TypeLits (KnownNat, Nat, type (+), type (-),
98103
type (*), type (<=), natVal)
104+
import GHC.TypeLits.KnownNat (KnownNat1(..), SNatKn(..), nameToSymbol)
99105
import GHC.TypeLits.Extra (CLog)
100106
import Test.QuickCheck.Arbitrary (Arbitrary (..), CoArbitrary (..),
101107
arbitraryBoundedIntegral,
@@ -111,9 +117,10 @@ import Clash.Class.BitPack.BitIndex (replaceBit)
111117
import Clash.Sized.Internal (formatRange)
112118
import {-# SOURCE #-} Clash.Sized.Internal.BitVector (BitVector (BV), high, low, undefError)
113119
import qualified Clash.Sized.Internal.BitVector as BV
114-
import Clash.Promoted.Nat (SNat(..), snatToNum, natToInteger, leToPlusKN)
120+
import Clash.Promoted.Nat (SNat(..), SNatLE(..), snatToNum, natToInteger, leToPlusKN, compareSNat)
115121
import Clash.XException
116122
(ShowX (..), NFDataX (..), errorX, showsPrecXWith, rwhnfX, seqX)
123+
import Unsafe.Coerce (unsafeCoerce)
117124

118125
{- $setup
119126
>>> import Clash.Sized.Internal.Index
@@ -184,10 +191,28 @@ instance NFData (Index n) where
184191
-- NOINLINE is needed so that Clash doesn't trip on the "Index ~# Integer"
185192
-- coercion
186193

187-
instance (KnownNat n, 1 <= n) => BitPack (Index n) where
188-
type BitSize (Index n) = CLog 2 n
189-
pack = packXWith pack#
190-
unpack = unpack#
194+
instance KnownNat n => BitPack (Index n) where
195+
type BitSize (Index n) = BitSizeIndex n
196+
pack = case compareSNat (SNat @1) (SNat @n) of
197+
SNatGT -> const 0
198+
SNatLE | Dict <- fact @n -> packXWith pack#
199+
unpack = case compareSNat (SNat @1) (SNat @n) of
200+
SNatGT -> const undefined
201+
SNatLE | Dict <- fact @n -> unpack#
202+
203+
type family BitSizeIndex (n :: Nat) where
204+
BitSizeIndex 0 = 0
205+
BitSizeIndex n = CLog 2 n
206+
207+
instance KnownNat n => KnownNat1 $(nameToSymbol ''BitSizeIndex) n where
208+
natSing1 = let n = natVal (Proxy @n)
209+
in SNatKn $ if n == 0
210+
then 0
211+
else fromInteger $ toInteger $ integerLog2 n
212+
{-# INLINE natSing1 #-}
213+
214+
fact :: forall n. 1 <= n => Dict (CLog 2 n ~ BitSizeIndex n)
215+
fact = unsafeCoerce (Dict :: Dict (0~0))
191216

192217
-- | Safely convert an `SNat` value to an `Index`
193218
fromSNat :: (KnownNat m, n + 1 <= m) => SNat n -> Index m

0 commit comments

Comments
 (0)