| Copyright | (C) 2013-2016 University of Twente |
|---|---|
| License | BSD2 (see the file LICENSE) |
| Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
| Safe Haskell | Trustworthy |
| Language | Haskell2010 |
| Extensions |
|
Clash.Sized.BitVector
Description
Bit
Bit
Instances
Construction
Initialisation
BitVector
data BitVector (n :: Nat) Source #
A vector of bits.
- Bit indices are descending
Numinstance performs unsigned arithmetic.
BitVector has the type role
>>>:i BitVectortype role BitVector nominal ...
as it is not safe to coerce between different size BitVector. To change the
size, use the functions in the Resize class.
Instances
Accessors
Length information
Construction
bLit :: String -> ExpQ Source #
Create a binary literal
>>>$(bLit "1001")0b1001
NB: You can also just write:
>>>0b1001 :: BitVector 40b1001
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.
N.B.: 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.
Concatenation
(++#) :: KnownNat m => BitVector n -> BitVector m -> BitVector (n + m) Source #
Concatenate two BitVectors
Pattern matching
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 variablesaa :: BitVector 2andbbb :: BitVector 3with 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