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 | MagicHash |
Synopsis
- data Bit
- high :: Bit
- low :: Bit
- data BitVector (n :: Nat)
- size# :: KnownNat n => BitVector n -> Int
- maxIndex# :: KnownNat n => BitVector n -> Int
- bLit :: forall n. KnownNat n => String -> Q (TExp (BitVector n))
- (++#) :: KnownNat m => BitVector n -> BitVector m -> BitVector (n + m)
- bitPattern :: String -> Q Pat
Bit
Bit
Instances
Construction
Initialisation
BitVector
data BitVector (n :: Nat) Source #
A vector of bits.
- Bit indices are descending
Num
instance performs unsigned arithmetic.
Instances
Accessors
Length information
Construction
bLit :: forall n. 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
Also bLit
can handle don't care bits:
>>>
$$(bLit "1.0.") :: BitVector 4
1.0.
Concatenation
(++#) :: KnownNat m => BitVector n -> BitVector m -> BitVector (n + m) Source #
Concatenate two BitVector
s
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, or '.'
for bits which are not matched.
The following example matches a byte against two bit patterns where some bits are relevant and others are not:
decode :: Unsigned 8 -> Maybe Bool decode $(bitPattern "00...110") = Just True decode $(bitPattern "10..0001") = Just False decode _ = Nothing