| Copyright | © Edward Kmett 2010-2015 © Eric Mertens 2014 Johan Kiviniemi 2013 |
|---|---|
| License | BSD3 |
| Maintainer | Edward Kmett <ekmett@gmail.com> |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Ersatz.Bits
Description
Bit1 .. Bit8 represent fixed length bit vectors.
The most significant bit comes first.
Bit1 and Bit2 have modular arithmetic
(the result has the same width as the arguments, overflow is ignored).
Bits is an arbitrary length natural number type.
The least significant bit comes first.
Bits has full arithmetic
(the result has large enough width so that there is no overflow).
Synopsis
- newtype Bit1 = Bit1 Bit
- data Bit2 = Bit2 !Bit !Bit
- data Bit3 = Bit3 !Bit !Bit !Bit
- data Bit4 = Bit4 !Bit !Bit !Bit !Bit
- data Bit5 = Bit5 !Bit !Bit !Bit !Bit !Bit
- data Bit6 = Bit6 !Bit !Bit !Bit !Bit !Bit !Bit
- data Bit7 = Bit7 !Bit !Bit !Bit !Bit !Bit !Bit !Bit
- data Bit8 = Bit8 !Bit !Bit !Bit !Bit !Bit !Bit !Bit !Bit
- newtype Bits = Bits [Bit]
- class HasBits a where
- isEven :: HasBits b => b -> Bit
- isOdd :: HasBits b => b -> Bit
- sumBit :: Foldable t => t Bit -> Bits
- sumBits :: (Foldable t, HasBits a) => t a -> Bits
- fullAdder :: Bit -> Bit -> Bit -> (Bit, Bit)
- halfAdder :: Bit -> Bit -> (Bit, Bit)
Fixed length bit vectors
Instances
| Generic Bit1 Source # | |||||
Defined in Ersatz.Bits Associated Types
| |||||
| Num Bit1 Source # | This instance provides modular arithmetic (overflow is ignored). | ||||
| Show Bit1 Source # | |||||
| Boolean Bit1 Source # | |||||
Defined in Ersatz.Bits Methods (&&) :: Bit1 -> Bit1 -> Bit1 Source # (||) :: Bit1 -> Bit1 -> Bit1 Source # (==>) :: Bit1 -> Bit1 -> Bit1 Source # and :: Foldable t => t Bit1 -> Bit1 Source # or :: Foldable t => t Bit1 -> Bit1 Source # nand :: Foldable t => t Bit1 -> Bit1 Source # nor :: Foldable t => t Bit1 -> Bit1 Source # all :: Foldable t => (a -> Bit1) -> t a -> Bit1 Source # any :: Foldable t => (a -> Bit1) -> t a -> Bit1 Source # | |||||
| HasBits Bit1 Source # | |||||
| Codec Bit1 Source # | |||||
| Equatable Bit1 Source # | |||||
| Orderable Bit1 Source # | |||||
| Variable Bit1 Source # | |||||
| type Rep Bit1 Source # | |||||
Defined in Ersatz.Bits | |||||
| type Decoded Bit1 Source # | |||||
Defined in Ersatz.Bits | |||||
Instances
Instances
| Generic Bit3 Source # | |||||
Defined in Ersatz.Bits Associated Types
| |||||
| Show Bit3 Source # | |||||
| Boolean Bit3 Source # | |||||
Defined in Ersatz.Bits Methods (&&) :: Bit3 -> Bit3 -> Bit3 Source # (||) :: Bit3 -> Bit3 -> Bit3 Source # (==>) :: Bit3 -> Bit3 -> Bit3 Source # and :: Foldable t => t Bit3 -> Bit3 Source # or :: Foldable t => t Bit3 -> Bit3 Source # nand :: Foldable t => t Bit3 -> Bit3 Source # nor :: Foldable t => t Bit3 -> Bit3 Source # all :: Foldable t => (a -> Bit3) -> t a -> Bit3 Source # any :: Foldable t => (a -> Bit3) -> t a -> Bit3 Source # | |||||
| HasBits Bit3 Source # | |||||
| Codec Bit3 Source # | |||||
| Equatable Bit3 Source # | |||||
| Orderable Bit3 Source # | |||||
| Variable Bit3 Source # | |||||
| type Rep Bit3 Source # | |||||
Defined in Ersatz.Bits type Rep Bit3 = D1 ('MetaData "Bit3" "Ersatz.Bits" "ersatz-0.6-AqdcKC2j1aSLWyGA90SA2m" 'False) (C1 ('MetaCons "Bit3" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit)))) | |||||
| type Decoded Bit3 Source # | |||||
Defined in Ersatz.Bits | |||||
Instances
| Generic Bit4 Source # | |||||
Defined in Ersatz.Bits Associated Types
| |||||
| Show Bit4 Source # | |||||
| Boolean Bit4 Source # | |||||
Defined in Ersatz.Bits Methods (&&) :: Bit4 -> Bit4 -> Bit4 Source # (||) :: Bit4 -> Bit4 -> Bit4 Source # (==>) :: Bit4 -> Bit4 -> Bit4 Source # and :: Foldable t => t Bit4 -> Bit4 Source # or :: Foldable t => t Bit4 -> Bit4 Source # nand :: Foldable t => t Bit4 -> Bit4 Source # nor :: Foldable t => t Bit4 -> Bit4 Source # all :: Foldable t => (a -> Bit4) -> t a -> Bit4 Source # any :: Foldable t => (a -> Bit4) -> t a -> Bit4 Source # | |||||
| HasBits Bit4 Source # | |||||
| Codec Bit4 Source # | |||||
| Equatable Bit4 Source # | |||||
| Orderable Bit4 Source # | |||||
| Variable Bit4 Source # | |||||
| type Rep Bit4 Source # | |||||
Defined in Ersatz.Bits type Rep Bit4 = D1 ('MetaData "Bit4" "Ersatz.Bits" "ersatz-0.6-AqdcKC2j1aSLWyGA90SA2m" 'False) (C1 ('MetaCons "Bit4" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit)))) | |||||
| type Decoded Bit4 Source # | |||||
Defined in Ersatz.Bits | |||||
Instances
| Generic Bit5 Source # | |||||
Defined in Ersatz.Bits Associated Types
| |||||
| Show Bit5 Source # | |||||
| Boolean Bit5 Source # | |||||
Defined in Ersatz.Bits Methods (&&) :: Bit5 -> Bit5 -> Bit5 Source # (||) :: Bit5 -> Bit5 -> Bit5 Source # (==>) :: Bit5 -> Bit5 -> Bit5 Source # and :: Foldable t => t Bit5 -> Bit5 Source # or :: Foldable t => t Bit5 -> Bit5 Source # nand :: Foldable t => t Bit5 -> Bit5 Source # nor :: Foldable t => t Bit5 -> Bit5 Source # all :: Foldable t => (a -> Bit5) -> t a -> Bit5 Source # any :: Foldable t => (a -> Bit5) -> t a -> Bit5 Source # | |||||
| HasBits Bit5 Source # | |||||
| Codec Bit5 Source # | |||||
| Equatable Bit5 Source # | |||||
| Orderable Bit5 Source # | |||||
| Variable Bit5 Source # | |||||
| type Rep Bit5 Source # | |||||
Defined in Ersatz.Bits type Rep Bit5 = D1 ('MetaData "Bit5" "Ersatz.Bits" "ersatz-0.6-AqdcKC2j1aSLWyGA90SA2m" 'False) (C1 ('MetaCons "Bit5" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit))))) | |||||
| type Decoded Bit5 Source # | |||||
Defined in Ersatz.Bits | |||||
Instances
| Generic Bit6 Source # | |||||
Defined in Ersatz.Bits Associated Types
| |||||
| Show Bit6 Source # | |||||
| Boolean Bit6 Source # | |||||
Defined in Ersatz.Bits Methods (&&) :: Bit6 -> Bit6 -> Bit6 Source # (||) :: Bit6 -> Bit6 -> Bit6 Source # (==>) :: Bit6 -> Bit6 -> Bit6 Source # and :: Foldable t => t Bit6 -> Bit6 Source # or :: Foldable t => t Bit6 -> Bit6 Source # nand :: Foldable t => t Bit6 -> Bit6 Source # nor :: Foldable t => t Bit6 -> Bit6 Source # all :: Foldable t => (a -> Bit6) -> t a -> Bit6 Source # any :: Foldable t => (a -> Bit6) -> t a -> Bit6 Source # | |||||
| HasBits Bit6 Source # | |||||
| Codec Bit6 Source # | |||||
| Equatable Bit6 Source # | |||||
| Orderable Bit6 Source # | |||||
| Variable Bit6 Source # | |||||
| type Rep Bit6 Source # | |||||
Defined in Ersatz.Bits type Rep Bit6 = D1 ('MetaData "Bit6" "Ersatz.Bits" "ersatz-0.6-AqdcKC2j1aSLWyGA90SA2m" 'False) (C1 ('MetaCons "Bit6" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit))))) | |||||
| type Decoded Bit6 Source # | |||||
Defined in Ersatz.Bits | |||||
Instances
| Generic Bit7 Source # | |||||
Defined in Ersatz.Bits Associated Types
| |||||
| Show Bit7 Source # | |||||
| Boolean Bit7 Source # | |||||
Defined in Ersatz.Bits Methods (&&) :: Bit7 -> Bit7 -> Bit7 Source # (||) :: Bit7 -> Bit7 -> Bit7 Source # (==>) :: Bit7 -> Bit7 -> Bit7 Source # and :: Foldable t => t Bit7 -> Bit7 Source # or :: Foldable t => t Bit7 -> Bit7 Source # nand :: Foldable t => t Bit7 -> Bit7 Source # nor :: Foldable t => t Bit7 -> Bit7 Source # all :: Foldable t => (a -> Bit7) -> t a -> Bit7 Source # any :: Foldable t => (a -> Bit7) -> t a -> Bit7 Source # | |||||
| HasBits Bit7 Source # | |||||
| Codec Bit7 Source # | |||||
| Equatable Bit7 Source # | |||||
| Orderable Bit7 Source # | |||||
| Variable Bit7 Source # | |||||
| type Rep Bit7 Source # | |||||
Defined in Ersatz.Bits type Rep Bit7 = D1 ('MetaData "Bit7" "Ersatz.Bits" "ersatz-0.6-AqdcKC2j1aSLWyGA90SA2m" 'False) (C1 ('MetaCons "Bit7" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit))))) | |||||
| type Decoded Bit7 Source # | |||||
Defined in Ersatz.Bits | |||||
Instances
| Generic Bit8 Source # | |||||
Defined in Ersatz.Bits Associated Types
| |||||
| Show Bit8 Source # | |||||
| Boolean Bit8 Source # | |||||
Defined in Ersatz.Bits Methods (&&) :: Bit8 -> Bit8 -> Bit8 Source # (||) :: Bit8 -> Bit8 -> Bit8 Source # (==>) :: Bit8 -> Bit8 -> Bit8 Source # and :: Foldable t => t Bit8 -> Bit8 Source # or :: Foldable t => t Bit8 -> Bit8 Source # nand :: Foldable t => t Bit8 -> Bit8 Source # nor :: Foldable t => t Bit8 -> Bit8 Source # all :: Foldable t => (a -> Bit8) -> t a -> Bit8 Source # any :: Foldable t => (a -> Bit8) -> t a -> Bit8 Source # | |||||
| HasBits Bit8 Source # | |||||
| Codec Bit8 Source # | |||||
| Equatable Bit8 Source # | |||||
| Orderable Bit8 Source # | |||||
| Variable Bit8 Source # | |||||
| type Rep Bit8 Source # | |||||
Defined in Ersatz.Bits type Rep Bit8 = D1 ('MetaData "Bit8" "Ersatz.Bits" "ersatz-0.6-AqdcKC2j1aSLWyGA90SA2m" 'False) (C1 ('MetaCons "Bit8" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bit))))) | |||||
| type Decoded Bit8 Source # | |||||
Defined in Ersatz.Bits | |||||
Variable length bit vectors
A container of Bits that is suitable for comparisons and arithmetic. Bits are stored
with least significant bit first to enable phantom false values
to be truncated.
Instances
| Num Bits Source # | This instance provides full arithmetic. The result has large enough width so that there is no overflow. Subtraction is modified: Width of
|
| Show Bits Source # | |
| HasBits Bits Source # | |
| Codec Bits Source # | |
| Equatable Bits Source # | |
| Orderable Bits Source # | |
| type Decoded Bits Source # | |
Defined in Ersatz.Bits | |
class HasBits a where Source #
HasBits provides the bits method for embedding
fixed with numeric encoding types into the arbitrary width
Bits type.
sumBits :: (Foldable t, HasBits a) => t a -> Bits Source #
Compute the sum of a source of Bits values.
Adders
Compute the sum and carry bit from adding three bits.