clash-prelude-1.8.2: Clash: a functional hardware description language - Prelude library
Copyright(C) 2013-2016 University of Twente
2019 Gergő Érdi
2016-2019 Myrtle Software Ltd
2021-2024 QBayLogic B.V.
2023 Nadia Chambers
LicenseBSD2 (see the file LICENSE)
MaintainerQBayLogic B.V. <[email protected]>
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
  • MultiWayIf
  • BinaryLiterals
  • TypeApplications

Clash.Sized.Internal.BitVector

Description

 
Synopsis

Bit

data Bit Source #

A single bit

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.

Constructors

Bit

The constructor, Bit, and the fields, unsafeMask# and unsafeToInteger#, are not synthesizable.

Instances

Instances details
AutoReg Bit Source # 
Instance details

Defined in Clash.Class.AutoReg.Internal

Methods

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

BitPack Bit Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize Bit 
Instance details

Defined in Clash.Class.BitPack.Internal

type BitSize Bit = 1
Bundle Bit Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom Bit 
Instance details

Defined in Clash.Signal.Bundle

type Unbundled dom Bit = Signal dom Bit

Methods

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

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

Bundle Bit Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

type Unbundled dom d Bit 
Instance details

Defined in Clash.Signal.Delayed.Bundle

type Unbundled dom d Bit = DSignal dom d Bit

Methods

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

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

NFDataX Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

ShowX Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Default Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

def :: Bit #

NFData Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

rnf :: Bit -> () #

Bits Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

(.&.) :: Bit -> Bit -> Bit #

(.|.) :: Bit -> Bit -> Bit #

xor :: Bit -> Bit -> Bit #

complement :: Bit -> Bit #

shift :: Bit -> Int -> Bit #

rotate :: Bit -> Int -> Bit #

zeroBits :: Bit #

bit :: Int -> Bit #

setBit :: Bit -> Int -> Bit #

clearBit :: Bit -> Int -> Bit #

complementBit :: Bit -> Int -> Bit #

testBit :: Bit -> Int -> Bool #

bitSizeMaybe :: Bit -> Maybe Int #

bitSize :: Bit -> Int #

isSigned :: Bit -> Bool #

shiftL :: Bit -> Int -> Bit #

unsafeShiftL :: Bit -> Int -> Bit #

shiftR :: Bit -> Int -> Bit #

unsafeShiftR :: Bit -> Int -> Bit #

rotateL :: Bit -> Int -> Bit #

rotateR :: Bit -> Int -> Bit #

popCount :: Bit -> Int #

FiniteBits Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Data Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

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

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

toConstr :: Bit -> Constr #

dataTypeOf :: Bit -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

minBound :: Bit #

maxBound :: Bit #

Enum Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

succ :: Bit -> Bit #

pred :: Bit -> Bit #

toEnum :: Int -> Bit #

fromEnum :: Bit -> Int #

enumFrom :: Bit -> [Bit] #

enumFromThen :: Bit -> Bit -> [Bit] #

enumFromTo :: Bit -> Bit -> [Bit] #

enumFromThenTo :: Bit -> Bit -> Bit -> [Bit] #

Generic Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Associated Types

type Rep Bit 
Instance details

Defined in Clash.Sized.Internal.BitVector

type Rep Bit = D1 ('MetaData "Bit" "Clash.Sized.Internal.BitVector" "clash-prelude-1.8.2-5TjnxEb2Rn58GfkYf0UYjY" 'False) (C1 ('MetaCons "Bit" 'PrefixI 'True) (S1 ('MetaSel ('Just "unsafeMask#") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word) :*: S1 ('MetaSel ('Just "unsafeToInteger#") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word)))

Methods

from :: Bit -> Rep Bit x #

to :: Rep Bit x -> Bit #

Num Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

(+) :: Bit -> Bit -> Bit #

(-) :: Bit -> Bit -> Bit #

(*) :: Bit -> Bit -> Bit #

negate :: Bit -> Bit #

abs :: Bit -> Bit #

signum :: Bit -> Bit #

fromInteger :: Integer -> Bit #

Integral Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

quot :: Bit -> Bit -> Bit #

rem :: Bit -> Bit -> Bit #

div :: Bit -> Bit -> Bit #

mod :: Bit -> Bit -> Bit #

quotRem :: Bit -> Bit -> (Bit, Bit) #

divMod :: Bit -> Bit -> (Bit, Bit) #

toInteger :: Bit -> Integer #

Real Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

toRational :: Bit -> Rational #

Show Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

showsPrec :: Int -> Bit -> ShowS #

show :: Bit -> String #

showList :: [Bit] -> ShowS #

Eq Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

(==) :: Bit -> Bit -> Bool #

(/=) :: Bit -> Bit -> Bool #

Ord Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

compare :: Bit -> Bit -> Ordering #

(<) :: Bit -> Bit -> Bool #

(<=) :: Bit -> Bit -> Bool #

(>) :: Bit -> Bit -> Bool #

(>=) :: Bit -> Bit -> Bool #

max :: Bit -> Bit -> Bit #

min :: Bit -> Bit -> Bit #

Lift Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

lift :: Quote m => Bit -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Bit -> Code m Bit #

type BitSize Bit Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

type BitSize Bit = 1
type Rep Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

type Rep Bit = D1 ('MetaData "Bit" "Clash.Sized.Internal.BitVector" "clash-prelude-1.8.2-5TjnxEb2Rn58GfkYf0UYjY" 'False) (C1 ('MetaCons "Bit" 'PrefixI 'True) (S1 ('MetaSel ('Just "unsafeMask#") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word) :*: S1 ('MetaSel ('Just "unsafeToInteger#") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word)))
type TryDomain t Bit Source # 
Instance details

Defined in Clash.Class.HasDomain.HasSingleDomain

type Unbundled dom Bit Source # 
Instance details

Defined in Clash.Signal.Bundle

type Unbundled dom Bit = Signal dom Bit
type Unbundled dom d Bit Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

type Unbundled dom d Bit = DSignal dom d Bit

Construction

high :: Bit Source #

logic '1'

low :: Bit Source #

logic '0'

Type classes

Eq

eq## :: Bit -> Bit -> Bool Source #

Ord

lt## :: Bit -> Bit -> Bool Source #

ge## :: Bit -> Bit -> Bool Source #

gt## :: Bit -> Bit -> Bool Source #

le## :: Bit -> Bit -> Bool Source #

Enum

Num

Bits

and## :: Bit -> Bit -> Bit Source #

or## :: Bit -> Bit -> Bit Source #

xor## :: Bit -> Bit -> Bit Source #

BitPack

BitVector

data BitVector (n :: Nat) Source #

A vector of bits

  • Bit indices are descending
  • Num instance performs unsigned arithmetic.

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.

BitVector has the type role

>>> :i BitVector
type role BitVector nominal
...

as it is not safe to coerce between different sizes of BitVector. To change the size, use the functions in the Resize class.

Constructors

BV

The constructor, BV, and the fields, unsafeMask and unsafeToNatural, are not synthesizable.

Instances

Instances details
Resize BitVector Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

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

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

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

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

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

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

Defined in Clash.Sized.Internal.BitVector

Methods

lift :: Quote m => BitVector n -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => BitVector n -> Code m (BitVector n) #

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

Defined in Clash.Sized.Internal.BitVector

Methods

arbitrary :: Gen (BitVector n) #

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

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

Defined in Clash.Sized.Internal.BitVector

Methods

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

KnownNat n => AutoReg (BitVector n) Source # 
Instance details

Defined in Clash.Class.AutoReg.Internal

Methods

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

KnownNat n => BitPack (BitVector n) Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

Associated Types

type BitSize (BitVector n) 
Instance details

Defined in Clash.Class.BitPack.Internal

type BitSize (BitVector n) = n
KnownNat n => Counter (BitVector n) Source # 
Instance details

Defined in Clash.Class.Counter.Internal

KnownNat n => SaturatingNum (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

KnownNat n => Parity (BitVector n) Source # 
Instance details

Defined in Clash.Class.Parity

Bundle (BitVector n) Source # 
Instance details

Defined in Clash.Signal.Bundle

Methods

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

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

Bundle (BitVector n) Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Methods

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

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

KnownNat n => NFDataX (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

KnownNat n => ShowX (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Default (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

def :: BitVector n #

NFData (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

rnf :: BitVector n -> () #

KnownNat n => Bits (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

KnownNat n => FiniteBits (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

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

Defined in Clash.Sized.Internal.BitVector

Methods

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

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

toConstr :: BitVector n -> Constr #

dataTypeOf :: BitVector n -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Clash.Sized.Internal.BitVector

KnownNat n => Enum (BitVector n) Source #

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

Instance details

Defined in Clash.Sized.Internal.BitVector

Generic (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Associated Types

type Rep (BitVector n) 
Instance details

Defined in Clash.Sized.Internal.BitVector

type Rep (BitVector n) = D1 ('MetaData "BitVector" "Clash.Sized.Internal.BitVector" "clash-prelude-1.8.2-5TjnxEb2Rn58GfkYf0UYjY" 'False) (C1 ('MetaCons "BV" 'PrefixI 'True) (S1 ('MetaSel ('Just "unsafeMask") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Natural) :*: S1 ('MetaSel ('Just "unsafeToNatural") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Natural)))

Methods

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

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

KnownNat n => Num (BitVector n) Source #

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.BitVector

KnownNat n => Integral (BitVector 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.BitVector

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

Defined in Clash.Sized.Internal.BitVector

KnownNat n => Show (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

KnownNat n => Eq (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

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

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

KnownNat n => Ord (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

KnownNat n => Ixed (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

(KnownNat m, KnownNat n) => ExtendingNum (BitVector m) (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Associated Types

type AResult (BitVector m) (BitVector n) 
Instance details

Defined in Clash.Sized.Internal.BitVector

type AResult (BitVector m) (BitVector n) = BitVector (Max m n + 1)
type MResult (BitVector m) (BitVector n) 
Instance details

Defined in Clash.Sized.Internal.BitVector

type MResult (BitVector m) (BitVector n) = BitVector (m + n)
type Unbundled dom d (BitVector n) Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

type Unbundled dom d (BitVector n) = DSignal dom d (BitVector n)
type TryDomain t (BitVector n) Source # 
Instance details

Defined in Clash.Class.HasDomain.HasSingleDomain

type Unbundled dom (BitVector n) Source # 
Instance details

Defined in Clash.Signal.Bundle

type Unbundled dom (BitVector n) = Signal dom (BitVector n)
type BitSize (BitVector n) Source # 
Instance details

Defined in Clash.Class.BitPack.Internal

type BitSize (BitVector n) = n
type Rep (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

type Rep (BitVector n) = D1 ('MetaData "BitVector" "Clash.Sized.Internal.BitVector" "clash-prelude-1.8.2-5TjnxEb2Rn58GfkYf0UYjY" 'False) (C1 ('MetaCons "BV" 'PrefixI 'True) (S1 ('MetaSel ('Just "unsafeMask") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Natural) :*: S1 ('MetaSel ('Just "unsafeToNatural") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Natural)))
type Index (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

type Index (BitVector n) = Int
type IxValue (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

type IxValue (BitVector n) = Bit
type AResult (BitVector m) (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

type AResult (BitVector m) (BitVector n) = BitVector (Max m n + 1)
type MResult (BitVector m) (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

type MResult (BitVector m) (BitVector n) = BitVector (m + n)

Accessors

size# :: forall (n :: Nat). KnownNat n => BitVector n -> Int Source #

maxIndex# :: forall (n :: Nat). KnownNat n => BitVector n -> Int Source #

Construction

bLit :: String -> ExpQ Source #

Create a binary literal

>>> $(bLit "1001")
0b1001

NB: You can also just write:

>>> 0b1001 :: BitVector 4
0b1001

The advantage of bLit is that you can use computations to create the string literal:

>>> import qualified Data.List as List
>>> $(bLit (List.replicate 4 '1'))
0b1111

Also bLit can handle don't care bits:

>>> $(bLit "1.0.")
0b1.0.

NB: From Clash 1.6 an onwards bLit will deduce the size of the BitVector from the given string and annotate the splice it produces accordingly.

hLit :: String -> ExpQ Source #

Create a hexadecimal literal

>>> $(hLit "dead")
0b1101_1110_1010_1101

Don't care digits set 4 bits:

>>> $(hLit "de..")
0b1101_1110_...._....

oLit :: String -> ExpQ Source #

Create an octal literal

>>> $(oLit "5234")
0b1010_1001_1100

Don't care digits set 3 bits:

>>> $(oLit "52..")
0b1010_10.._....

undefined# :: forall (n :: Nat). KnownNat n => BitVector n Source #

Create a BitVector with all its bits undefined

Concatenation

(++#) :: forall (m :: Nat) (n :: Nat). KnownNat m => BitVector n -> BitVector m -> BitVector (n + m) Source #

Concatenate two BitVectors

Reduction

reduceAnd# :: forall (n :: Nat). KnownNat n => BitVector n -> Bit Source #

reduceOr# :: forall (n :: Nat). KnownNat n => BitVector n -> Bit Source #

reduceXor# :: forall (n :: Nat). KnownNat n => BitVector n -> Bit Source #

Indexing

index# :: forall (n :: Nat). KnownNat n => BitVector n -> Int -> Bit Source #

replaceBit# :: forall (n :: Nat). KnownNat n => BitVector n -> Int -> Bit -> BitVector n Source #

setSlice# :: forall (m :: Natural) (i :: Natural) (n :: Nat). SNat ((m + 1) + i) -> BitVector ((m + 1) + i) -> SNat m -> SNat n -> BitVector ((m + 1) - n) -> BitVector ((m + 1) + i) Source #

slice# :: forall (m :: Natural) (i :: Natural) (n :: Nat). BitVector ((m + 1) + i) -> SNat m -> SNat n -> BitVector ((m + 1) - n) Source #

split# :: forall (n :: Nat) (m :: Natural). KnownNat n => BitVector (m + n) -> (BitVector m, BitVector n) Source #

msb# :: forall (n :: Nat). KnownNat n => BitVector n -> Bit Source #

MSB

lsb# :: forall (n :: Nat). BitVector n -> Bit Source #

LSB

Type classes

Eq

eq# :: forall (n :: Nat). KnownNat n => BitVector n -> BitVector n -> Bool Source #

neq# :: forall (n :: Nat). KnownNat n => BitVector n -> BitVector n -> Bool Source #

isLike# :: forall (n :: Nat). KnownNat n => BitVector n -> BitVector n -> Bool Source #

Check if one BitVector is similar to another, interpreting undefined bits in the second argument as being "don't care" bits. This is a more lenient version of (==), similar to std_match in VHDL or casez in Verilog.

>>> let expected = $(bLit "1.")
>>> let checked  = $(bLit "11")
>>> checked  `isLike#` expected
True
>>> expected `isLike#` checked
False

NB: Not synthesizable

Ord

lt# :: forall (n :: Nat). KnownNat n => BitVector n -> BitVector n -> Bool Source #

ge# :: forall (n :: Nat). KnownNat n => BitVector n -> BitVector n -> Bool Source #

gt# :: forall (n :: Nat). KnownNat n => BitVector n -> BitVector n -> Bool Source #

le# :: forall (n :: Nat). KnownNat n => BitVector n -> BitVector n -> Bool Source #

Enum

toEnum# :: forall (n :: Nat). KnownNat n => Int -> BitVector n Source #

fromEnum# :: forall (n :: Nat). KnownNat n => BitVector n -> Int Source #

Enum (not synthesizable)

enumFrom# :: forall (n :: Nat). KnownNat n => BitVector n -> [BitVector n] Source #

enumFromThen# :: forall (n :: Nat). KnownNat n => BitVector n -> BitVector n -> [BitVector n] Source #

enumFromTo# :: forall (n :: Nat). KnownNat n => BitVector n -> BitVector n -> [BitVector n] Source #

enumFromThenTo# :: forall (n :: Nat). KnownNat n => BitVector n -> BitVector n -> BitVector n -> [BitVector n] Source #

Bounded

minBound# :: forall (n :: Nat). BitVector n Source #

maxBound# :: forall (n :: Nat). KnownNat n => BitVector n Source #

Num

(+#) :: forall (n :: Nat). KnownNat n => BitVector n -> BitVector n -> BitVector n Source #

(-#) :: forall (n :: Nat). KnownNat n => BitVector n -> BitVector n -> BitVector n Source #

(*#) :: forall (n :: Nat). KnownNat n => BitVector n -> BitVector n -> BitVector n Source #

negate# :: forall (n :: Nat). KnownNat n => BitVector n -> BitVector n Source #

fromInteger# :: forall (n :: Nat). KnownNat n => Natural -> Integer -> BitVector n Source #

ExtendingNum

plus# :: forall (m :: Nat) (n :: Nat). (KnownNat m, KnownNat n) => BitVector m -> BitVector n -> BitVector (Max m n + 1) Source #

minus# :: forall (m :: Nat) (n :: Nat). (KnownNat m, KnownNat n) => BitVector m -> BitVector n -> BitVector (Max m n + 1) Source #

times# :: forall (m :: Nat) (n :: Nat). (KnownNat m, KnownNat n) => BitVector m -> BitVector n -> BitVector (m + n) Source #

Integral

quot# :: forall (n :: Nat). KnownNat n => BitVector n -> BitVector n -> BitVector n Source #

rem# :: forall (n :: Nat). KnownNat n => BitVector n -> BitVector n -> BitVector n Source #

toInteger# :: forall (n :: Nat). KnownNat n => BitVector n -> Integer Source #

Bits

and# :: forall (n :: Nat). KnownNat n => BitVector n -> BitVector n -> BitVector n Source #

or# :: forall (n :: Nat). KnownNat n => BitVector n -> BitVector n -> BitVector n Source #

xor# :: forall (n :: Nat). KnownNat n => BitVector n -> BitVector n -> BitVector n Source #

complement# :: forall (n :: Nat). KnownNat n => BitVector n -> BitVector n Source #

shiftL# :: forall (n :: Nat). KnownNat n => BitVector n -> Int -> BitVector n Source #

shiftR# :: forall (n :: Nat). KnownNat n => BitVector n -> Int -> BitVector n Source #

rotateL# :: forall (n :: Nat). KnownNat n => BitVector n -> Int -> BitVector n Source #

rotateR# :: forall (n :: Nat). KnownNat n => BitVector n -> Int -> BitVector n Source #

popCountBV :: forall (n :: Nat). KnownNat n => BitVector (n + 1) -> Index (n + 2) Source #

FiniteBits

countLeadingZerosBV :: forall (n :: Nat). KnownNat n => BitVector n -> Index (n + 1) Source #

countTrailingZerosBV :: forall (n :: Nat). KnownNat n => BitVector n -> Index (n + 1) Source #

Resize

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

QuickCheck

shrinkSizedUnsigned :: forall (n :: Nat) p. (KnownNat n, Integral (p n)) => p n -> [p n] Source #

shrink for sized unsigned types

Other

undefError :: forall (n :: Nat) a. KnownNat n => String -> [BitVector n] -> a Source #

checkUnpackUndef Source #

Arguments

:: forall (n :: Nat) a. (KnownNat n, Typeable a) 
=> (BitVector n -> a)

unpack function

-> BitVector n 
-> a 

Implement BitVector undefinedness checking for unpack functions

bitPattern :: String -> Q Pat Source #

Template Haskell macro for generating a pattern matching on some bits of a value.

This macro compiles to an efficient view pattern that matches the bits of a given value against the bits specified in the pattern. The scrutinee can be any type that is an instance of the Num, Bits and Eq typeclasses.

The bit pattern is specified by a string which contains:

  • '0' or '1' for matching a bit
  • '.' for bits which are not matched (wildcard)
  • '_' can be used as a separator similar to the NumericUnderscores language extension
  • lowercase alphabetical characters can be used to bind some bits to variables. For example "0aab11bb" will bind two variables aa :: BitVector 2 and bbb :: BitVector 3 with their values set by the corresponding bits

The following example matches a byte against two bit patterns where some bits are relevant and others are not while binding two variables aa and bb:

  decode :: Unsigned 8 -> Maybe Bool
  decode $(bitPattern "00.._.110") = Just True
  decode $(bitPattern "10.._0001") = Just False
  decode $(bitPattern "aa.._b0b1") = Just (aa + bb > 1)
  decode _ = Nothing

xToBV :: forall (n :: Nat). KnownNat n => BitVector n -> BitVector n Source #