clash-prelude-0.99.2: CAES Language for Synchronous Hardware - Prelude library

Copyright(C) 2013-2016 University of Twente
2016 Myrtle Software Ltd
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellUnsafe
LanguageHaskell2010
Extensions
  • UndecidableInstances
  • MonoLocalBinds
  • TemplateHaskell
  • TemplateHaskellQuotes
  • ScopedTypeVariables
  • TypeFamilies
  • DataKinds
  • DeriveDataTypeable
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • MagicHash
  • KindSignatures
  • GeneralizedNewtypeDeriving
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll
  • TypeApplications

Clash.Sized.Internal.BitVector

Contents

Description

 
Synopsis

Bit

newtype Bit Source #

Bit

Constructors

Bit

The constructor, Bit, and the field, unsafeToInteger#, are not synthesisable.

Instances
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] #

Eq Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

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

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

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 #

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 :: (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 #

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 #

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 #

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 #

Lift Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

lift :: Bit -> Q Exp #

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

NFData Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

rnf :: Bit -> () #

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

BitPack Bit Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

type BitSize Bit :: Nat Source #

Bundle Bit Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled domain Bit = (res :: *) Source #

Methods

bundle :: Unbundled domain Bit -> Signal domain Bit Source #

unbundle :: Signal domain Bit -> Unbundled domain Bit Source #

type BitSize Bit Source # 
Instance details

Defined in Clash.Class.BitPack

type BitSize Bit = 1
type Unbundled domain Bit Source # 
Instance details

Defined in Clash.Signal.Bundle

type Unbundled domain Bit = Signal domain 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 #

Num

Bits

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

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

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

BitPack

BitVector

newtype BitVector (n :: Nat) Source #

A vector of bits.

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

Constructors

BV

The constructor, BV, and the field, unsafeToInteger, are not synthesisable.

Instances
Resize BitVector Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

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

Instance details

Defined in Clash.Sized.Internal.BitVector

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 => Integral (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 :: (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 => Num (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Ord (BitVector n) Source # 
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 => Lift (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

lift :: BitVector n -> Q Exp #

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

NFData (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

rnf :: BitVector n -> () #

KnownNat n => SaturatingNum (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

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

Defined in Clash.Sized.Internal.BitVector

Methods

ix :: Index (BitVector n) -> Traversal' (BitVector n) (IxValue (BitVector n))

Default (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

def :: 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

BitPack (BitVector n) Source # 
Instance details

Defined in Clash.Class.BitPack

Associated Types

type BitSize (BitVector n) :: Nat Source #

Bundle (BitVector n) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled domain (BitVector n) = (res :: *) Source #

Methods

bundle :: Unbundled domain (BitVector n) -> Signal domain (BitVector n) Source #

unbundle :: Signal domain (BitVector n) -> Unbundled domain (BitVector n) Source #

(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) :: * Source #

type MResult (BitVector m) (BitVector n) :: * Source #

type Unbundled domain (BitVector n) Source # 
Instance details

Defined in Clash.Signal.Bundle

type Unbundled domain (BitVector n) = Signal domain (BitVector n)
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 BitSize (BitVector n) Source # 
Instance details

Defined in Clash.Class.BitPack

type BitSize (BitVector n) = n
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

Construction

bLit :: KnownNat n => String -> Q (TExp (BitVector n)) Source #

Create a binary literal

>>> $$(bLit "1001") :: BitVector 4
1001
>>> $$(bLit "1001") :: BitVector 3
001

NB: You can also just write:

>>> 0b1001 :: BitVector 4
1001

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')) :: BitVector 4
1111

Concatenation

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

Concatenate two BitVectors

Reduction

Indexing

setSlice# :: BitVector ((m + 1) + i) -> SNat m -> SNat n -> BitVector ((m + 1) - n) -> BitVector ((m + 1) + i) Source #

slice# :: BitVector ((m + 1) + i) -> SNat m -> SNat n -> BitVector ((m + 1) - n) Source #

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

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

MSB

Type classes

Eq

Ord

Enum (not synthesisable)

Bounded

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

Num

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

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

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

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

ExtendingNum

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

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

Integral

Bits

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

FiniteBits

Resize

resize# :: forall n m. KnownNat m => BitVector n -> BitVector m Source #

QuickCheck

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

shrink for sized unsigned types