clash-prelude-1.7.0: Clash: a functional hardware description language - Prelude library
Copyright(C) 2013-2016 University of Twente
2016-2019 Myrtle Software Ltd
2021-2023 QBayLogic B.V.
LicenseBSD2 (see the file LICENSE)
MaintainerQBayLogic B.V. <devops@qbaylogic.com>
Safe HaskellUnsafe
LanguageHaskell2010
Extensions
  • Cpp
  • UndecidableInstances
  • MonoLocalBinds
  • TemplateHaskell
  • TemplateHaskellQuotes
  • ScopedTypeVariables
  • BangPatterns
  • TypeFamilies
  • ViewPatterns
  • DataKinds
  • InstanceSigs
  • StandaloneDeriving
  • DeriveDataTypeable
  • DeriveFunctor
  • DeriveTraversable
  • DeriveFoldable
  • DeriveGeneric
  • DefaultSignatures
  • DeriveAnyClass
  • DeriveLift
  • DerivingStrategies
  • FlexibleContexts
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • MagicHash
  • KindSignatures
  • RoleAnnotations
  • PostfixOperators
  • TupleSections
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll
  • BinaryLiterals
  • TypeApplications

Clash.Sized.Internal.Index

Description

 
Synopsis

Datatypes

newtype Index (n :: Nat) Source #

Arbitrarily-bounded unsigned integer represented by ceil(log_2(n)) bits

Given an upper bound n, an Index n number has a range of: [0 .. n-1]

>>> maxBound :: Index 8
7
>>> minBound :: Index 8
0
>>> read (show (maxBound :: Index 8)) :: Index 8
7
>>> 1 + 2 :: Index 8
3
>>> 2 + 6 :: Index 8
*** Exception: X: Clash.Sized.Index: result 8 is out of bounds: [0..7]
...
>>> 1 - 3 :: Index 8
*** Exception: X: Clash.Sized.Index: result -2 is out of bounds: [0..7]
...
>>> 2 * 3 :: Index 8
6
>>> 2 * 4 :: Index 8
*** Exception: X: Clash.Sized.Index: result 8 is out of bounds: [0..7]
...

NB: The usual Haskell method of converting an integral numeric type to another, fromIntegral, is not well suited for Clash as it will go through Integer which is arbitrarily bounded in HDL. Instead use bitCoerce and the Resize class.

Index has the type role

>>> :i Index
type role Index nominal
...

as it is not safe to coerce between Indexes with different ranges. To change the size, use the functions in the Resize class.

Constructors

I

The constructor, I, and the field, unsafeToInteger, are not synthesizable.

Instances

Instances details
Resize Index Source # 
Instance details

Defined in Clash.Sized.Internal.Index

Methods

resize :: forall (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b) => Index a -> Index b Source #

extend :: forall (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b) => Index a -> Index (b + a) Source #

zeroExtend :: forall (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b) => Index a -> Index (b + a) Source #

signExtend :: forall (a :: Nat) (b :: Nat). (KnownNat a, KnownNat b) => Index a -> Index (b + a) Source #

truncateB :: forall (a :: Nat) (b :: Nat). KnownNat a => Index (a + b) -> Index a Source #

KnownNat n => Lift (Index n :: Type) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

Methods

lift :: Index n -> Q Exp #

liftTyped :: Index n -> Q (TExp (Index n)) #

KnownNat n => Bounded (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

Methods

minBound :: Index n #

maxBound :: Index n #

KnownNat n => Enum (Index n) Source #

The functions: enumFrom, enumFromThen, enumFromTo, and enumFromThenTo, are not synthesizable.

Instance details

Defined in Clash.Sized.Internal.Index

Methods

succ :: Index n -> Index n #

pred :: Index n -> Index n #

toEnum :: Int -> Index n #

fromEnum :: Index n -> Int #

enumFrom :: Index n -> [Index n] #

enumFromThen :: Index n -> Index n -> [Index n] #

enumFromTo :: Index n -> Index n -> [Index n] #

enumFromThenTo :: Index n -> Index n -> Index n -> [Index n] #

Eq (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

Methods

(==) :: Index n -> Index n -> Bool #

(/=) :: Index n -> Index n -> Bool #

KnownNat n => Integral (Index n) Source #

NB: toInteger/fromIntegral can cause unexpected truncation, as Integer is arbitrarily bounded during synthesis. Prefer bitCoerce and the Resize class.

Instance details

Defined in Clash.Sized.Internal.Index

Methods

quot :: Index n -> Index n -> Index n #

rem :: Index n -> Index n -> Index n #

div :: Index n -> Index n -> Index n #

mod :: Index n -> Index n -> Index n #

quotRem :: Index n -> Index n -> (Index n, Index n) #

divMod :: Index n -> Index n -> (Index n, Index n) #

toInteger :: Index n -> Integer #

KnownNat n => Data (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Index n -> c (Index n) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Index n) #

toConstr :: Index n -> Constr #

dataTypeOf :: Index n -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Index n)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Index n)) #

gmapT :: (forall b. Data b => b -> b) -> Index n -> Index n #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Index n -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Index n -> r #

gmapQ :: (forall d. Data d => d -> u) -> Index n -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Index n -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Index n -> m (Index n) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Index n -> m (Index n) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Index n -> m (Index n) #

KnownNat n => Num (Index n) Source #

Operators report an error on overflow and underflow

NB: fromInteger/fromIntegral can cause unexpected truncation, as Integer is arbitrarily bounded during synthesis. Prefer bitCoerce and the Resize class.

Instance details

Defined in Clash.Sized.Internal.Index

Methods

(+) :: Index n -> Index n -> Index n #

(-) :: Index n -> Index n -> Index n #

(*) :: Index n -> Index n -> Index n #

negate :: Index n -> Index n #

abs :: Index n -> Index n #

signum :: Index n -> Index n #

fromInteger :: Integer -> Index n #

Ord (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

Methods

compare :: Index n -> Index n -> Ordering #

(<) :: Index n -> Index n -> Bool #

(<=) :: Index n -> Index n -> Bool #

(>) :: Index n -> Index n -> Bool #

(>=) :: Index n -> Index n -> Bool #

max :: Index n -> Index n -> Index n #

min :: Index n -> Index n -> Index n #

KnownNat n => Read (Index n) Source #

None of the Read class' methods are synthesizable.

Instance details

Defined in Clash.Sized.Internal.Index

KnownNat n => Real (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

Methods

toRational :: Index n -> Rational #

Show (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

Methods

showsPrec :: Int -> Index n -> ShowS #

show :: Index n -> String #

showList :: [Index n] -> ShowS #

KnownNat n => Ix (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

Methods

range :: (Index n, Index n) -> [Index n] #

index :: (Index n, Index n) -> Index n -> Int #

unsafeIndex :: (Index n, Index n) -> Index n -> Int #

inRange :: (Index n, Index n) -> Index n -> Bool #

rangeSize :: (Index n, Index n) -> Int #

unsafeRangeSize :: (Index n, Index n) -> Int #

Generic (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

Associated Types

type Rep (Index n) :: Type -> Type #

Methods

from :: Index n -> Rep (Index n) x #

to :: Rep (Index n) x -> Index n #

KnownNat n => Arbitrary (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

Methods

arbitrary :: Gen (Index n) #

shrink :: Index n -> [Index n] #

KnownNat n => CoArbitrary (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

Methods

coarbitrary :: Index n -> Gen b -> Gen b #

KnownNat n => PrintfArg (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

(KnownNat n, 1 <= n) => Bits (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

Methods

(.&.) :: Index n -> Index n -> Index n #

(.|.) :: Index n -> Index n -> Index n #

xor :: Index n -> Index n -> Index n #

complement :: Index n -> Index n #

shift :: Index n -> Int -> Index n #

rotate :: Index n -> Int -> Index n #

zeroBits :: Index n #

bit :: Int -> Index n #

setBit :: Index n -> Int -> Index n #

clearBit :: Index n -> Int -> Index n #

complementBit :: Index n -> Int -> Index n #

testBit :: Index n -> Int -> Bool #

bitSizeMaybe :: Index n -> Maybe Int #

bitSize :: Index n -> Int #

isSigned :: Index n -> Bool #

shiftL :: Index n -> Int -> Index n #

unsafeShiftL :: Index n -> Int -> Index n #

shiftR :: Index n -> Int -> Index n #

unsafeShiftR :: Index n -> Int -> Index n #

rotateL :: Index n -> Int -> Index n #

rotateR :: Index n -> Int -> Index n #

popCount :: Index n -> Int #

(KnownNat n, 1 <= n) => FiniteBits (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

KnownNat n => Default (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

Methods

def :: Index n #

NFData (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

Methods

rnf :: Index n -> () #

(KnownNat n, 1 <= n) => SaturatingNum (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

NFDataX (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

ShowX (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

(KnownNat n, 1 <= n) => BitPack (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

Associated Types

type BitSize (Index n) :: Nat Source #

(KnownNat n, 1 <= n) => Parity (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

Methods

even :: Index n -> Bool Source #

odd :: Index n -> Bool Source #

Bundle (Index n) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (Index n) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (Index n) -> Signal dom (Index n) Source #

unbundle :: forall (dom :: Domain). Signal dom (Index n) -> Unbundled dom (Index n) Source #

Bundle (Index n) Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

type Unbundled dom d (Index n) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain) (d :: Nat). Unbundled dom d (Index n) -> DSignal dom d (Index n) Source #

unbundle :: forall (dom :: Domain) (d :: Nat). DSignal dom d (Index n) -> Unbundled dom d (Index n) Source #

(1 <= n, KnownNat n) => Counter (Index n) Source # 
Instance details

Defined in Clash.Class.Counter.Internal

AutoReg (Index n) Source # 
Instance details

Defined in Clash.Class.AutoReg.Internal

Methods

autoReg :: forall (dom :: Domain). (HasCallStack, KnownDomain dom) => Clock dom -> Reset dom -> Enable dom -> Index n -> Signal dom (Index n) -> Signal dom (Index n) Source #

KnownNat m => Exp (Index m) Source # 
Instance details

Defined in Clash.Class.Exp

Associated Types

type ExpResult (Index m) n Source #

Methods

(^) :: forall (n :: Nat). Index m -> SNat n -> ExpResult (Index m) n Source #

ExtendingNum (Index m) (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

Associated Types

type AResult (Index m) (Index n) Source #

type MResult (Index m) (Index n) Source #

Methods

add :: Index m -> Index n -> AResult (Index m) (Index n) Source #

sub :: Index m -> Index n -> AResult (Index m) (Index n) Source #

mul :: Index m -> Index n -> MResult (Index m) (Index n) Source #

type Unbundled dom d (Index n) Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

type Unbundled dom d (Index n) = DSignal dom d (Index n)
type Unbundled dom (Index n) Source # 
Instance details

Defined in Clash.Signal.Bundle

type Unbundled dom (Index n) = Signal dom (Index n)
type TryDomain t (Index n) Source # 
Instance details

Defined in Clash.Class.HasDomain.HasSingleDomain

type TryDomain t (Index n) = 'NotFound
type Rep (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

type Rep (Index n) = D1 ('MetaData "Index" "Clash.Sized.Internal.Index" "clash-prelude-1.7.0-inplace" 'True) (C1 ('MetaCons "I" 'PrefixI 'True) (S1 ('MetaSel ('Just "unsafeToInteger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))
type BitSize (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

type BitSize (Index n) = CLog 2 n
type ExpResult (Index m) n Source # 
Instance details

Defined in Clash.Class.Exp

type ExpResult (Index m) n = Index (Max 2 (m ^ n))
type AResult (Index m) (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

type AResult (Index m) (Index n) = Index ((m + n) - 1)
type MResult (Index m) (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

type MResult (Index m) (Index n) = Index (((m - 1) * (n - 1)) + 1)

Construction

fromSNat :: (KnownNat m, (n + 1) <= m) => SNat n -> Index m Source #

Safely convert an SNat value to an Index

Accessors

Length information

size# :: (KnownNat n, 1 <= n) => Index n -> Int Source #

Type classes

BitPack

unpack# :: (KnownNat n, 1 <= n) => BitVector (CLog 2 n) -> Index n Source #

Eq

eq# :: Index n -> Index n -> Bool Source #

neq# :: Index n -> Index n -> Bool Source #

Ord

lt# :: Index n -> Index n -> Bool Source #

ge# :: Index n -> Index n -> Bool Source #

gt# :: Index n -> Index n -> Bool Source #

le# :: Index n -> Index n -> Bool Source #

Enum

toEnum# :: forall n. KnownNat n => Int -> Index n Source #

fromEnum# :: forall n. KnownNat n => Index n -> Int Source #

Enum (not synthesizable)

enumFrom# :: forall n. KnownNat n => Index n -> [Index n] Source #

enumFromThen# :: forall n. KnownNat n => Index n -> Index n -> [Index n] Source #

enumFromTo# :: Index n -> Index n -> [Index n] Source #

enumFromThenTo# :: Index n -> Index n -> Index n -> [Index n] Source #

Bounded

maxBound# :: forall n. KnownNat n => Index n Source #

Num

(+#) :: KnownNat n => Index n -> Index n -> Index n Source #

(-#) :: KnownNat n => Index n -> Index n -> Index n Source #

(*#) :: KnownNat n => Index n -> Index n -> Index n Source #

ExtendingNum

plus# :: Index m -> Index n -> Index ((m + n) - 1) Source #

minus# :: Index m -> Index n -> Index ((m + n) - 1) Source #

times# :: Index m -> Index n -> Index (((m - 1) * (n - 1)) + 1) Source #

Integral

quot# :: Index n -> Index n -> Index n Source #

rem# :: Index n -> Index n -> Index n Source #

Resize