Skip to content
This repository was archived by the owner on Sep 7, 2018. It is now read-only.

Commit 24db559

Browse files
committed
Add safeIndexPow2 to safely index Vecs with 2^n elements
1 parent 2861fd0 commit 24db559

File tree

1 file changed

+26
-3
lines changed

1 file changed

+26
-3
lines changed

src/CLaSH/Sized/Vector.hs

+26-3
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,7 @@ module CLaSH.Sized.Vector
4141
-- ** Special folds
4242
, dfold, vfold
4343
-- ** Indexing 'Vec'tors
44-
, (!!), replace, maxIndex, length
44+
, (!!), safeIndexPow2, replace, maxIndex, length
4545
-- ** Generating 'Vec'tors
4646
, replicate, repeat, iterate, iterateI, generate, generateI
4747
-- ** Misc
@@ -56,8 +56,8 @@ import Data.Default (Default (..))
5656
import qualified Data.Foldable as F
5757
import Data.Proxy (Proxy (..))
5858
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 (^))
6161
import GHC.Base (Int(I#),Int#,isTrue#)
6262
import GHC.Prim ((==#),(<#),(-#))
6363
import Language.Haskell.TH (ExpQ)
@@ -789,6 +789,29 @@ index_int xs i@(I# n0)
789789
(!!) :: (KnownNat n, Integral i) => Vec n a -> i -> a
790790
xs !! i = index_int xs (fromIntegral i)
791791

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+
792815
{-# NOINLINE maxIndex #-}
793816
-- | Index (subscript) of the last element in a 'Vec'tor
794817
--

0 commit comments

Comments
 (0)