@@ -41,7 +41,7 @@ module CLaSH.Sized.Vector
41
41
-- ** Special folds
42
42
, dfold , vfold
43
43
-- ** Indexing 'Vec'tors
44
- , (!!) , replace , maxIndex , length
44
+ , (!!) , safeIndexPow2 , replace , maxIndex , length
45
45
-- ** Generating 'Vec'tors
46
46
, replicate , repeat , iterate , iterateI , generate , generateI
47
47
-- ** Misc
@@ -56,8 +56,8 @@ import Data.Default (Default (..))
56
56
import qualified Data.Foldable as F
57
57
import Data.Proxy (Proxy (.. ))
58
58
import Data.Singletons.Prelude (TyFun ,Apply ,type ($ ))
59
- import GHC.TypeLits (CmpNat , KnownNat , Nat , type ( + ), type ( * ) ,
60
- natVal )
59
+ import GHC.TypeLits (CmpNat , KnownNat , Nat , natVal ,
60
+ type ( + ), type ( * ), type ( ^ ) )
61
61
import GHC.Base (Int (I #),Int #,isTrue #)
62
62
import GHC.Prim ((==#) ,(<#) ,(-#) )
63
63
import Language.Haskell.TH (ExpQ )
@@ -789,6 +789,29 @@ index_int xs i@(I# n0)
789
789
(!!) :: (KnownNat n , Integral i ) => Vec n a -> i -> a
790
790
xs !! i = index_int xs (fromIntegral i)
791
791
792
+ {-# INLINE safeIndexPow2 #-}
793
+ -- | Vector index (subscript) operator.
794
+ --
795
+ -- Unlike '(!!)', it enforces that the vector has two raised to the number of
796
+ -- bits of the index. Use 'Unsigned' or 'BitVector' to rule out negative
797
+ -- numbers, and ensure a 1-1 mapping between indices and elements in the vector.
798
+ --
799
+ -- __NB__: vector elements have an __ASCENDING__ subscript starting from 0 and
800
+ -- ending at 'maxIndex'.
801
+ --
802
+ -- >>> (1:>2:>3:>4:>Nil) `safeIndexPow2` (0 :: Unsigned 2)
803
+ -- 1
804
+ -- >>> (1:>2:>3:>4:>Nil) `safeIndexPow2` (fromIntegral (maxIndex (1:>2:>3:>4:>Nil)) :: Unsigned 2)
805
+ -- 4
806
+ -- >>> (1:>2:>3:>4:>Nil) `safeIndexPow2` (1 :: Unsigned 2)
807
+ -- 2
808
+ safeIndexPow2 :: KnownNat (2 ^ BitSize i )
809
+ => Integral i
810
+ => Vec (2 ^ BitSize i ) a
811
+ -> i
812
+ -> a
813
+ safeIndexPow2 = (!!)
814
+
792
815
{-# NOINLINE maxIndex #-}
793
816
-- | Index (subscript) of the last element in a 'Vec'tor
794
817
--
0 commit comments