clash-prelude-1.4.4: Clash: a functional hardware description language - Prelude library
Copyright(C) 2013-2016 University of Twente
2019 Gergő Érdi
2016-2019 Myrtle Software Ltd
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.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
  • TupleSections
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll
  • BinaryLiterals
  • TypeApplications

Clash.Sized.Internal.BitVector

Description

 
Synopsis

Bit

data Bit Source #

Bit

Constructors

Bit

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

Instances

Instances details
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 :: 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 #

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 #

Generic Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Associated Types

type Rep Bit :: Type -> Type #

Methods

from :: Bit -> Rep Bit x #

to :: Rep Bit x -> 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

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

NFDataX Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

ShowX Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

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 dom Bit = (res :: Type) Source #

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 = (res :: Type) Source #

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 #

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 #

Lift Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

lift :: Bit -> Q Exp #

liftTyped :: Bit -> Q (TExp Bit) #

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.4.4-inplace" '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 BitSize Bit Source # 
Instance details

Defined in Clash.Class.BitPack

type BitSize Bit = 1
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 #

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.

BitVector has the type role

>>> :i BitVector
type 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.

Constructors

BV

The constructor, BV, and the field, 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 :: Nat). 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 :: BitVector n -> Q Exp #

liftTyped :: BitVector n -> Q (TExp (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

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

Defined in Clash.Sized.Internal.BitVector

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

Generic (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Associated Types

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

Methods

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

to :: Rep (BitVector n) x -> 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 => 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

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

Defined in Clash.Sized.Internal.BitVector

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

Defined in Clash.Sized.Internal.BitVector

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

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

Defined in Clash.Class.BitPack

Associated Types

type BitSize (BitVector n) :: Nat Source #

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

Defined in Clash.Class.Parity

Bundle (BitVector n) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

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

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

Associated Types

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

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

Defined in Clash.Signal.Bundle

type Unbundled dom (BitVector n) = Signal dom (BitVector 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.4.4-inplace" '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 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 :: 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.

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

Create a BitVector with all its bits undefined

Concatenation

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

Concatenate two BitVectors

Reduction

Indexing

setSlice# :: forall m i n. SNat ((m + 1) + i) -> 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

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

Check if one BitVector is like another. NFDataX bits in the second argument are interpreted as don't care bits.

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

NB: Not synthesizable

Ord

Enum (not synthesizable)

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

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

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

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

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# :: (KnownNat m, KnownNat n) => 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

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

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

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

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

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

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

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

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

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

FiniteBits

Resize

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

QuickCheck

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

shrink for sized unsigned types

Other

checkUnpackUndef Source #

Arguments

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

unpack function

-> BitVector n 
-> a 

Implement BitVector undefinedness checking for unpack funtions

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